gogol-maps-engine-0.3.0: Google Maps Engine 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.MapsEngine

Contents

Description

The Google Maps Engine API allows developers to store and query geospatial vector and raster data.

See: Google Maps Engine API Reference

Synopsis

Service Configuration

mapsEngineService :: ServiceConfig Source #

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

OAuth Scopes

mapsEngineScope :: Proxy '["https://www.googleapis.com/auth/mapsengine"] Source #

View and manage your Google My Maps data

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

View your Google My Maps data

API Declaration

type MapsEngineAPI = MapsPermissionsListResource :<|> (MapsPermissionsBatchUpdateResource :<|> (MapsPermissionsBatchDeleteResource :<|> (MapsListResource :<|> (MapsListPublishedResource :<|> (MapsPatchResource :<|> (MapsGetResource :<|> (MapsGetPublishedResource :<|> (MapsCreateResource :<|> (MapsUnPublishResource :<|> (MapsDeleteResource :<|> (MapsPublishResource :<|> (TablesParentsListResource :<|> (TablesFeaturesListResource :<|> (TablesFeaturesBatchInsertResource :<|> (TablesFeaturesGetResource :<|> (TablesFeaturesBatchPatchResource :<|> (TablesFeaturesBatchDeleteResource :<|> (TablesFilesInsertResource :<|> (TablesPermissionsListResource :<|> (TablesPermissionsBatchUpdateResource :<|> (TablesPermissionsBatchDeleteResource :<|> (TablesListResource :<|> (TablesProcessResource :<|> (TablesPatchResource :<|> (TablesGetResource :<|> (TablesCreateResource :<|> (TablesUploadResource :<|> (TablesDeleteResource :<|> (LayersParentsListResource :<|> (LayersPermissionsListResource :<|> (LayersPermissionsBatchUpdateResource :<|> (LayersPermissionsBatchDeleteResource :<|> (LayersListResource :<|> (LayersListPublishedResource :<|> (LayersProcessResource :<|> (LayersPatchResource :<|> (LayersGetResource :<|> (LayersGetPublishedResource :<|> (LayersCreateResource :<|> (LayersUnPublishResource :<|> (LayersCancelProcessingResource :<|> (LayersDeleteResource :<|> (LayersPublishResource :<|> (RastersParentsListResource :<|> (RastersFilesInsertResource :<|> (RastersPermissionsListResource :<|> (RastersPermissionsBatchUpdateResource :<|> (RastersPermissionsBatchDeleteResource :<|> (RastersListResource :<|> (RastersProcessResource :<|> (RastersPatchResource :<|> (RastersGetResource :<|> (RastersUploadResource :<|> (RastersDeleteResource :<|> (AssetsParentsListResource :<|> (AssetsPermissionsListResource :<|> (AssetsListResource :<|> (AssetsGetResource :<|> (RasterCollectionsParentsListResource :<|> (RasterCollectionsPermissionsListResource :<|> (RasterCollectionsPermissionsBatchUpdateResource :<|> (RasterCollectionsPermissionsBatchDeleteResource :<|> (RasterCollectionsRastersListResource :<|> (RasterCollectionsRastersBatchInsertResource :<|> (RasterCollectionsRastersBatchDeleteResource :<|> (RasterCollectionsListResource :<|> (RasterCollectionsProcessResource :<|> (RasterCollectionsPatchResource :<|> (RasterCollectionsGetResource :<|> (RasterCollectionsCreateResource :<|> (RasterCollectionsCancelProcessingResource :<|> (RasterCollectionsDeleteResource :<|> (ProjectsIconsListResource :<|> (ProjectsIconsGetResource :<|> (ProjectsIconsCreateResource :<|> ProjectsListResource))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))))) Source #

Represents the entirety of the methods and resources available for the Google Maps Engine API service.

Resources

mapsengine.assets.get

mapsengine.assets.list

mapsengine.assets.parents.list

mapsengine.assets.permissions.list

mapsengine.layers.cancelProcessing

mapsengine.layers.create

mapsengine.layers.delete

mapsengine.layers.get

mapsengine.layers.getPublished

mapsengine.layers.list

mapsengine.layers.listPublished

mapsengine.layers.parents.list

mapsengine.layers.patch

mapsengine.layers.permissions.batchDelete

mapsengine.layers.permissions.batchUpdate

mapsengine.layers.permissions.list

mapsengine.layers.process

mapsengine.layers.publish

mapsengine.layers.unpublish

mapsengine.maps.create

mapsengine.maps.delete

mapsengine.maps.get

mapsengine.maps.getPublished

mapsengine.maps.list

mapsengine.maps.listPublished

mapsengine.maps.patch

mapsengine.maps.permissions.batchDelete

mapsengine.maps.permissions.batchUpdate

mapsengine.maps.permissions.list

mapsengine.maps.publish

mapsengine.maps.unpublish

mapsengine.projects.icons.create

mapsengine.projects.icons.get

mapsengine.projects.icons.list

mapsengine.projects.list

mapsengine.rasterCollections.cancelProcessing

mapsengine.rasterCollections.create

mapsengine.rasterCollections.delete

mapsengine.rasterCollections.get

mapsengine.rasterCollections.list

mapsengine.rasterCollections.parents.list

mapsengine.rasterCollections.patch

mapsengine.rasterCollections.permissions.batchDelete

mapsengine.rasterCollections.permissions.batchUpdate

mapsengine.rasterCollections.permissions.list

mapsengine.rasterCollections.process

mapsengine.rasterCollections.rasters.batchDelete

mapsengine.rasterCollections.rasters.batchInsert

mapsengine.rasterCollections.rasters.list

mapsengine.rasters.delete

mapsengine.rasters.files.insert

mapsengine.rasters.get

mapsengine.rasters.list

mapsengine.rasters.parents.list

mapsengine.rasters.patch

mapsengine.rasters.permissions.batchDelete

mapsengine.rasters.permissions.batchUpdate

mapsengine.rasters.permissions.list

mapsengine.rasters.process

mapsengine.rasters.upload

mapsengine.tables.create

mapsengine.tables.delete

mapsengine.tables.features.batchDelete

mapsengine.tables.features.batchInsert

mapsengine.tables.features.batchPatch

mapsengine.tables.features.get

mapsengine.tables.features.list

mapsengine.tables.files.insert

mapsengine.tables.get

mapsengine.tables.list

mapsengine.tables.parents.list

mapsengine.tables.patch

mapsengine.tables.permissions.batchDelete

mapsengine.tables.permissions.batchUpdate

mapsengine.tables.permissions.list

mapsengine.tables.process

mapsengine.tables.upload

Types

ValueRange

data ValueRange Source #

Range of values used for scaling shapes. The min/max values will be drawn as shapes with the min/max size.

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.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "ValueRange'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_vrMax") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_vrMin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))))

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:

GeoJSONProperties

data GeoJSONProperties Source #

The properties associated with a feature.

See: geoJSONProperties smart constructor.

Instances

Eq GeoJSONProperties Source # 
Data GeoJSONProperties Source # 

Methods

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

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

toConstr :: GeoJSONProperties -> Constr #

dataTypeOf :: GeoJSONProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GeoJSONProperties Source # 
Generic GeoJSONProperties Source # 
ToJSON GeoJSONProperties Source # 
FromJSON GeoJSONProperties Source # 
type Rep GeoJSONProperties Source # 
type Rep GeoJSONProperties = D1 (MetaData "GeoJSONProperties" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" True) (C1 (MetaCons "GeoJSONProperties'" PrefixI True) (S1 (MetaSel (Just Symbol "_gjpAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

geoJSONProperties Source #

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

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

gjpAddtional :: Lens' GeoJSONProperties (HashMap Text JSONValue) Source #

An arbitrary key-value pair. The key must be the name of a column in the table's schema, and the type of the value must correspond to the type specified in the schema.

Feature

data Feature Source #

A feature within a table.

See: feature smart constructor.

Instances

Eq Feature Source # 

Methods

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

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

Data Feature Source # 

Methods

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

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

toConstr :: Feature -> Constr #

dataTypeOf :: Feature -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Feature Source # 
Generic Feature Source # 

Associated Types

type Rep Feature :: * -> * #

Methods

from :: Feature -> Rep Feature x #

to :: Rep Feature x -> Feature #

ToJSON Feature Source # 
FromJSON Feature Source # 
type Rep Feature Source # 
type Rep Feature = D1 (MetaData "Feature" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Feature'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fGeometry") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GeoJSONGeometry))) ((:*:) (S1 (MetaSel (Just Symbol "_fType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_fProperties") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GeoJSONProperties))))))

feature :: Feature Source #

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

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

fGeometry :: Lens' Feature (Maybe GeoJSONGeometry) Source #

The geometry member of this Feature.

fType :: Lens' Feature Text Source #

Identifies this object as a feature.

fProperties :: Lens' Feature (Maybe GeoJSONProperties) Source #

Key/value pairs of this Feature.

Parent

data Parent Source #

A list of the parents of an asset.

See: parent smart constructor.

Instances

Eq Parent Source # 

Methods

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

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

Data Parent Source # 

Methods

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

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

toConstr :: Parent -> Constr #

dataTypeOf :: Parent -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Parent Source # 
Generic Parent Source # 

Associated Types

type Rep Parent :: * -> * #

Methods

from :: Parent -> Rep Parent x #

to :: Rep Parent x -> Parent #

ToJSON Parent Source # 
FromJSON Parent Source # 
type Rep Parent Source # 
type Rep Parent = D1 (MetaData "Parent" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" True) (C1 (MetaCons "Parent'" PrefixI True) (S1 (MetaSel (Just Symbol "_pId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

parent :: Parent Source #

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

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

pId :: Lens' Parent (Maybe Text) Source #

The ID of this parent.

FeaturesBatchPatchRequest

data FeaturesBatchPatchRequest Source #

The request sent to features.BatchPatch.

See: featuresBatchPatchRequest smart constructor.

Instances

Eq FeaturesBatchPatchRequest Source # 
Data FeaturesBatchPatchRequest Source # 

Methods

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

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

toConstr :: FeaturesBatchPatchRequest -> Constr #

dataTypeOf :: FeaturesBatchPatchRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FeaturesBatchPatchRequest Source # 
Generic FeaturesBatchPatchRequest Source # 
ToJSON FeaturesBatchPatchRequest Source # 
FromJSON FeaturesBatchPatchRequest Source # 
type Rep FeaturesBatchPatchRequest Source # 
type Rep FeaturesBatchPatchRequest = D1 (MetaData "FeaturesBatchPatchRequest" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "FeaturesBatchPatchRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fbprFeatures") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Feature]))) (S1 (MetaSel (Just Symbol "_fbprNormalizeGeometries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))))

featuresBatchPatchRequest :: FeaturesBatchPatchRequest Source #

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

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

fbprNormalizeGeometries :: Lens' FeaturesBatchPatchRequest Bool Source #

If true, the server will normalize feature geometries. It is assumed that the South Pole is exterior to any polygons given. See here for a list of normalizations. If false, all feature geometries must be given already normalized. The points in all LinearRings must be listed in counter-clockwise order, and LinearRings may not intersect.

PermissionsBatchUpdateRequest

data PermissionsBatchUpdateRequest Source #

The request sent to mapsengine.permissions.batchUpdate.

See: permissionsBatchUpdateRequest smart constructor.

Instances

Eq PermissionsBatchUpdateRequest Source # 
Data PermissionsBatchUpdateRequest Source # 

Methods

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

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

toConstr :: PermissionsBatchUpdateRequest -> Constr #

dataTypeOf :: PermissionsBatchUpdateRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PermissionsBatchUpdateRequest Source # 
Generic PermissionsBatchUpdateRequest Source # 
ToJSON PermissionsBatchUpdateRequest Source # 
FromJSON PermissionsBatchUpdateRequest Source # 
type Rep PermissionsBatchUpdateRequest Source # 
type Rep PermissionsBatchUpdateRequest = D1 (MetaData "PermissionsBatchUpdateRequest" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" True) (C1 (MetaCons "PermissionsBatchUpdateRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_pburPermissions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Permission]))))

permissionsBatchUpdateRequest :: PermissionsBatchUpdateRequest Source #

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

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

pburPermissions :: Lens' PermissionsBatchUpdateRequest [Permission] Source #

The permissions to be inserted or updated.

RasterProcessingStatus

data RasterProcessingStatus Source #

The processing status of this Raster.

Constructors

Complete
complete
Failed
failed
NotReady
notReady
Processing
processing
Ready
ready

Instances

Enum RasterProcessingStatus Source # 
Eq RasterProcessingStatus Source # 
Data RasterProcessingStatus Source # 

Methods

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

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

toConstr :: RasterProcessingStatus -> Constr #

dataTypeOf :: RasterProcessingStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RasterProcessingStatus Source # 
Read RasterProcessingStatus Source # 
Show RasterProcessingStatus Source # 
Generic RasterProcessingStatus Source # 
Hashable RasterProcessingStatus Source # 
ToJSON RasterProcessingStatus Source # 
FromJSON RasterProcessingStatus Source # 
FromHttpApiData RasterProcessingStatus Source # 
ToHttpApiData RasterProcessingStatus Source # 
type Rep RasterProcessingStatus Source # 
type Rep RasterProcessingStatus = D1 (MetaData "RasterProcessingStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "Complete" PrefixI False) U1) (C1 (MetaCons "Failed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "NotReady" PrefixI False) U1) ((:+:) (C1 (MetaCons "Processing" PrefixI False) U1) (C1 (MetaCons "Ready" PrefixI False) U1))))

LayerProcessingStatus

data LayerProcessingStatus Source #

The processing status of this layer.

Constructors

LPSComplete
complete
LPSFailed
failed
LPSNotReady
notReady
LPSProcessing
processing
LPSReady
ready

Instances

Enum LayerProcessingStatus Source # 
Eq LayerProcessingStatus Source # 
Data LayerProcessingStatus Source # 

Methods

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

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

toConstr :: LayerProcessingStatus -> Constr #

dataTypeOf :: LayerProcessingStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LayerProcessingStatus Source # 
Read LayerProcessingStatus Source # 
Show LayerProcessingStatus Source # 
Generic LayerProcessingStatus Source # 
Hashable LayerProcessingStatus Source # 
ToJSON LayerProcessingStatus Source # 
FromJSON LayerProcessingStatus Source # 
FromHttpApiData LayerProcessingStatus Source # 
ToHttpApiData LayerProcessingStatus Source # 
type Rep LayerProcessingStatus Source # 
type Rep LayerProcessingStatus = D1 (MetaData "LayerProcessingStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "LPSComplete" PrefixI False) U1) (C1 (MetaCons "LPSFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LPSNotReady" PrefixI False) U1) ((:+:) (C1 (MetaCons "LPSProcessing" PrefixI False) U1) (C1 (MetaCons "LPSReady" PrefixI False) U1))))

ScaledShapeShape

data ScaledShapeShape Source #

Name of the shape.

Constructors

Circle
circle

Instances

Enum ScaledShapeShape Source # 
Eq ScaledShapeShape Source # 
Data ScaledShapeShape Source # 

Methods

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

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

toConstr :: ScaledShapeShape -> Constr #

dataTypeOf :: ScaledShapeShape -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ScaledShapeShape Source # 
Read ScaledShapeShape Source # 
Show ScaledShapeShape Source # 
Generic ScaledShapeShape Source # 
Hashable ScaledShapeShape Source # 
ToJSON ScaledShapeShape Source # 
FromJSON ScaledShapeShape Source # 
FromHttpApiData ScaledShapeShape Source # 
ToHttpApiData ScaledShapeShape Source # 
type Rep ScaledShapeShape Source # 
type Rep ScaledShapeShape = D1 (MetaData "ScaledShapeShape" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Circle" PrefixI False) U1)

PermissionsBatchDeleteRequest

data PermissionsBatchDeleteRequest Source #

The request sent to mapsengine.permissions.batchDelete.

See: permissionsBatchDeleteRequest smart constructor.

Instances

Eq PermissionsBatchDeleteRequest Source # 
Data PermissionsBatchDeleteRequest Source # 

Methods

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

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

toConstr :: PermissionsBatchDeleteRequest -> Constr #

dataTypeOf :: PermissionsBatchDeleteRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PermissionsBatchDeleteRequest Source # 
Generic PermissionsBatchDeleteRequest Source # 
ToJSON PermissionsBatchDeleteRequest Source # 
FromJSON PermissionsBatchDeleteRequest Source # 
type Rep PermissionsBatchDeleteRequest Source # 
type Rep PermissionsBatchDeleteRequest = D1 (MetaData "PermissionsBatchDeleteRequest" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" True) (C1 (MetaCons "PermissionsBatchDeleteRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_pbdrIds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))))

permissionsBatchDeleteRequest :: PermissionsBatchDeleteRequest Source #

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

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

pbdrIds :: Lens' PermissionsBatchDeleteRequest [Text] Source #

An array of permission ids to be removed. This could be the email address of the user or group this permission refers to, or the string "anyone" for public permissions.

RasterCollectionsListResponse

data RasterCollectionsListResponse Source #

The response returned by a call to raster_collections.List. Note: The list response does not include all the fields available in a raster collection. Refer to the RasterCollection resource description for details of the fields that are not included. You'll need to send a get request to retrieve the additional fields for each raster collection.

See: rasterCollectionsListResponse smart constructor.

Instances

Eq RasterCollectionsListResponse Source # 
Data RasterCollectionsListResponse Source # 

Methods

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

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

toConstr :: RasterCollectionsListResponse -> Constr #

dataTypeOf :: RasterCollectionsListResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RasterCollectionsListResponse Source # 
Generic RasterCollectionsListResponse Source # 
ToJSON RasterCollectionsListResponse Source # 
FromJSON RasterCollectionsListResponse Source # 
type Rep RasterCollectionsListResponse Source # 
type Rep RasterCollectionsListResponse = D1 (MetaData "RasterCollectionsListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "RasterCollectionsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rclrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bytes))) (S1 (MetaSel (Just Symbol "_rclrRasterCollections") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RasterCollection])))))

rasterCollectionsListResponse :: RasterCollectionsListResponse Source #

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

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

GeoJSONMultiLineStringType

data GeoJSONMultiLineStringType Source #

Identifies this object as a GeoJsonMultiLineString.

Constructors

MultiLineString
MultiLineString

Instances

Enum GeoJSONMultiLineStringType Source # 
Eq GeoJSONMultiLineStringType Source # 
Data GeoJSONMultiLineStringType Source # 

Methods

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

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

toConstr :: GeoJSONMultiLineStringType -> Constr #

dataTypeOf :: GeoJSONMultiLineStringType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GeoJSONMultiLineStringType Source # 
Read GeoJSONMultiLineStringType Source # 
Show GeoJSONMultiLineStringType Source # 
Generic GeoJSONMultiLineStringType Source # 
Hashable GeoJSONMultiLineStringType Source # 
ToJSON GeoJSONMultiLineStringType Source # 
FromJSON GeoJSONMultiLineStringType Source # 
FromHttpApiData GeoJSONMultiLineStringType Source # 
ToHttpApiData GeoJSONMultiLineStringType Source # 
type Rep GeoJSONMultiLineStringType Source # 
type Rep GeoJSONMultiLineStringType = D1 (MetaData "GeoJSONMultiLineStringType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "MultiLineString" PrefixI False) U1)

PermissionRole

data PermissionRole Source #

The type of access granted to this user or group.

Constructors

Owner
owner
Reader
reader
Viewer
viewer
Writer
writer

Instances

Enum PermissionRole Source # 
Eq PermissionRole Source # 
Data PermissionRole Source # 

Methods

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

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

toConstr :: PermissionRole -> Constr #

dataTypeOf :: PermissionRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PermissionRole Source # 
Read PermissionRole Source # 
Show PermissionRole Source # 
Generic PermissionRole Source # 

Associated Types

type Rep PermissionRole :: * -> * #

Hashable PermissionRole Source # 
ToJSON PermissionRole Source # 
FromJSON PermissionRole Source # 
FromHttpApiData PermissionRole Source # 
ToHttpApiData PermissionRole Source # 
type Rep PermissionRole Source # 
type Rep PermissionRole = D1 (MetaData "PermissionRole" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "Owner" PrefixI False) U1) (C1 (MetaCons "Reader" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Viewer" PrefixI False) U1) (C1 (MetaCons "Writer" PrefixI False) U1)))

ProjectsListResponse

data ProjectsListResponse Source #

The response returned by a call to projects.List.

See: projectsListResponse smart constructor.

Instances

Eq ProjectsListResponse Source # 
Data ProjectsListResponse Source # 

Methods

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

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

toConstr :: ProjectsListResponse -> Constr #

dataTypeOf :: ProjectsListResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ProjectsListResponse Source # 
Generic ProjectsListResponse Source # 
ToJSON ProjectsListResponse Source # 
FromJSON ProjectsListResponse Source # 
type Rep ProjectsListResponse Source # 
type Rep ProjectsListResponse = D1 (MetaData "ProjectsListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" True) (C1 (MetaCons "ProjectsListResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_plrProjects") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Project]))))

projectsListResponse :: ProjectsListResponse Source #

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

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

GeoJSONGeometry

data GeoJSONGeometry Source #

Instances

Eq GeoJSONGeometry Source # 
Data GeoJSONGeometry Source # 

Methods

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

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

toConstr :: GeoJSONGeometry -> Constr #

dataTypeOf :: GeoJSONGeometry -> DataType #

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

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

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

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

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

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

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

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

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

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

Show GeoJSONGeometry Source # 
Generic GeoJSONGeometry Source # 
ToJSON GeoJSONGeometry Source # 
FromJSON GeoJSONGeometry Source # 
type Rep GeoJSONGeometry Source # 
type Rep GeoJSONGeometry = D1 (MetaData "GeoJSONGeometry" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "GeoJSONGeometry'" PrefixI False) U1)

geoJSONGeometry :: GeoJSONGeometry Source #

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

MapLayer

data MapLayer Source #

Instances

Eq MapLayer Source # 
Data MapLayer Source # 

Methods

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

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

toConstr :: MapLayer -> Constr #

dataTypeOf :: MapLayer -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MapLayer Source # 
Generic MapLayer Source # 

Associated Types

type Rep MapLayer :: * -> * #

Methods

from :: MapLayer -> Rep MapLayer x #

to :: Rep MapLayer x -> MapLayer #

ToJSON MapLayer Source # 
FromJSON MapLayer Source # 
type Rep MapLayer Source # 

mapLayer :: MapLayer Source #

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

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

mlDefaultViewport :: Lens' MapLayer [Double] Source #

An array of four numbers (west, south, east, north) which defines the rectangular bounding box of the default viewport. The numbers represent latitude and longitude in decimal degrees.

mlVisibility :: Lens' MapLayer (Maybe Text) Source #

The visibility setting of this MapLayer. One of "defaultOn" or "defaultOff".

mlKey :: Lens' MapLayer (Maybe Text) Source #

A user defined alias for this MapLayer, specific to this Map.

mlName :: Lens' MapLayer (Maybe Text) Source #

The name of this MapLayer.

mlId :: Lens' MapLayer (Maybe Text) Source #

The ID of this MapLayer. This ID can be used to request more details about the layer.

mlType :: Lens' MapLayer (Maybe MapLayerType) Source #

Identifies this object as a MapLayer.

ZoomLevels

data ZoomLevels Source #

Zoom level range. Zoom levels are restricted between 0 and 24, inclusive.

See: zoomLevels smart constructor.

Instances

Eq ZoomLevels Source # 
Data ZoomLevels Source # 

Methods

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

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

toConstr :: ZoomLevels -> Constr #

dataTypeOf :: ZoomLevels -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ZoomLevels Source # 
Generic ZoomLevels Source # 

Associated Types

type Rep ZoomLevels :: * -> * #

ToJSON ZoomLevels Source # 
FromJSON ZoomLevels Source # 
type Rep ZoomLevels Source # 
type Rep ZoomLevels = D1 (MetaData "ZoomLevels" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "ZoomLevels'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_zlMax") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_zlMin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

zoomLevels :: ZoomLevels Source #

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

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

zlMax :: Lens' ZoomLevels (Maybe Int32) Source #

Maximum zoom level.

zlMin :: Lens' ZoomLevels (Maybe Int32) Source #

Minimum zoom level.

FeatureInfo

data FeatureInfo Source #

A feature info contains information about individual feature.

See: featureInfo smart constructor.

Instances

Eq FeatureInfo Source # 
Data FeatureInfo Source # 

Methods

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

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

toConstr :: FeatureInfo -> Constr #

dataTypeOf :: FeatureInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FeatureInfo Source # 
Generic FeatureInfo Source # 

Associated Types

type Rep FeatureInfo :: * -> * #

ToJSON FeatureInfo Source # 
FromJSON FeatureInfo Source # 
type Rep FeatureInfo Source # 
type Rep FeatureInfo = D1 (MetaData "FeatureInfo" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" True) (C1 (MetaCons "FeatureInfo'" PrefixI True) (S1 (MetaSel (Just Symbol "_fiContent") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

featureInfo :: FeatureInfo Source #

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

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

fiContent :: Lens' FeatureInfo (Maybe Text) Source #

HTML template of the info window. If not provided, a default template with all attributes will be generated.

AcquisitionTimePrecision

data AcquisitionTimePrecision Source #

The precision of acquisition time.

Constructors

Day
day
Hour
hour
Minute
minute
Month
month
Second
second
Year
year

Instances

Enum AcquisitionTimePrecision Source # 
Eq AcquisitionTimePrecision Source # 
Data AcquisitionTimePrecision Source # 

Methods

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

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

toConstr :: AcquisitionTimePrecision -> Constr #

dataTypeOf :: AcquisitionTimePrecision -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AcquisitionTimePrecision Source # 
Read AcquisitionTimePrecision Source # 
Show AcquisitionTimePrecision Source # 
Generic AcquisitionTimePrecision Source # 
Hashable AcquisitionTimePrecision Source # 
ToJSON AcquisitionTimePrecision Source # 
FromJSON AcquisitionTimePrecision Source # 
FromHttpApiData AcquisitionTimePrecision Source # 
ToHttpApiData AcquisitionTimePrecision Source # 
type Rep AcquisitionTimePrecision Source # 
type Rep AcquisitionTimePrecision = D1 (MetaData "AcquisitionTimePrecision" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "Day" PrefixI False) U1) ((:+:) (C1 (MetaCons "Hour" PrefixI False) U1) (C1 (MetaCons "Minute" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Month" PrefixI False) U1) ((:+:) (C1 (MetaCons "Second" PrefixI False) U1) (C1 (MetaCons "Year" PrefixI False) U1))))

SizeRange

data SizeRange Source #

Scaled shape size range in pixels. For circles, size corresponds to diameter.

See: sizeRange smart constructor.

Instances

Eq SizeRange Source # 
Data SizeRange Source # 

Methods

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

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

toConstr :: SizeRange -> Constr #

dataTypeOf :: SizeRange -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SizeRange Source # 
Generic SizeRange Source # 

Associated Types

type Rep SizeRange :: * -> * #

ToJSON SizeRange Source # 
FromJSON SizeRange Source # 
type Rep SizeRange Source # 
type Rep SizeRange = D1 (MetaData "SizeRange" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "SizeRange'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_srMax") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_srMin") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))))

sizeRange :: SizeRange Source #

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

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

srMax :: Lens' SizeRange (Maybe Double) Source #

Maximum size, in pixels.

srMin :: Lens' SizeRange (Maybe Double) Source #

Minimum size, in pixels.

ScalingFunctionScalingType

data ScalingFunctionScalingType Source #

The type of scaling function to use. Defaults to SQRT. Currently only linear and square root scaling are supported.

Constructors

Linear
linear
Sqrt
sqrt

Instances

Enum ScalingFunctionScalingType Source # 
Eq ScalingFunctionScalingType Source # 
Data ScalingFunctionScalingType Source # 

Methods

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

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

toConstr :: ScalingFunctionScalingType -> Constr #

dataTypeOf :: ScalingFunctionScalingType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ScalingFunctionScalingType Source # 
Read ScalingFunctionScalingType Source # 
Show ScalingFunctionScalingType Source # 
Generic ScalingFunctionScalingType Source # 
Hashable ScalingFunctionScalingType Source # 
ToJSON ScalingFunctionScalingType Source # 
FromJSON ScalingFunctionScalingType Source # 
FromHttpApiData ScalingFunctionScalingType Source # 
ToHttpApiData ScalingFunctionScalingType Source # 
type Rep ScalingFunctionScalingType Source # 
type Rep ScalingFunctionScalingType = D1 (MetaData "ScalingFunctionScalingType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "Linear" PrefixI False) U1) (C1 (MetaCons "Sqrt" PrefixI False) U1))

MapFolder

data MapFolder Source #

Instances

Eq MapFolder Source # 
Data MapFolder Source # 

Methods

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

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

toConstr :: MapFolder -> Constr #

dataTypeOf :: MapFolder -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MapFolder Source # 
Generic MapFolder Source # 

Associated Types

type Rep MapFolder :: * -> * #

ToJSON MapFolder Source # 
FromJSON MapFolder Source # 
type Rep MapFolder Source # 

mapFolder :: MapFolder Source #

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

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

mfExpandable :: Lens' MapFolder (Maybe Bool) Source #

The expandability setting of this MapFolder. If true, the folder can be expanded.

mfDefaultViewport :: Lens' MapFolder [Double] Source #

An array of four numbers (west, south, east, north) which defines the rectangular bounding box of the default viewport. The numbers represent latitude and longitude in decimal degrees.

mfVisibility :: Lens' MapFolder (Maybe Text) Source #

The visibility setting of this MapFolder. One of "defaultOn" or "defaultOff".

mfKey :: Lens' MapFolder (Maybe Text) Source #

A user defined alias for this MapFolder, specific to this Map.

mfName :: Lens' MapFolder (Maybe Text) Source #

The name of this MapFolder.

mfType :: Lens' MapFolder (Maybe MapFolderType) Source #

Identifies this object as a MapFolder.

AssetsListRole

data AssetsListRole Source #

The role parameter indicates that the response should only contain assets where the current user has the specified level of access.

Constructors

ALROwner

owner The user can read, write and administer the asset.

ALRReader

reader The user can read the asset.

ALRWriter

writer The user can read and write the asset.

Instances

Enum AssetsListRole Source # 
Eq AssetsListRole Source # 
Data AssetsListRole Source # 

Methods

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

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

toConstr :: AssetsListRole -> Constr #

dataTypeOf :: AssetsListRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord AssetsListRole Source # 
Read AssetsListRole Source # 
Show AssetsListRole Source # 
Generic AssetsListRole Source # 

Associated Types

type Rep AssetsListRole :: * -> * #

Hashable AssetsListRole Source # 
ToJSON AssetsListRole Source # 
FromJSON AssetsListRole Source # 
FromHttpApiData AssetsListRole Source # 
ToHttpApiData AssetsListRole Source # 
type Rep AssetsListRole Source # 
type Rep AssetsListRole = D1 (MetaData "AssetsListRole" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "ALROwner" PrefixI False) U1) ((:+:) (C1 (MetaCons "ALRReader" PrefixI False) U1) (C1 (MetaCons "ALRWriter" PrefixI False) U1)))

RastersListProcessingStatus

data RastersListProcessingStatus Source #

Constructors

RLPSComplete

complete The raster has completed processing.

RLPSFailed

failed The raster has failed processing.

RLPSNotReady

notReady The raster is not ready for processing.

RLPSProcessing

processing The raster is processing.

RLPSReady

ready The raster is ready for processing.

Instances

Enum RastersListProcessingStatus Source # 
Eq RastersListProcessingStatus Source # 
Data RastersListProcessingStatus Source # 

Methods

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

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

toConstr :: RastersListProcessingStatus -> Constr #

dataTypeOf :: RastersListProcessingStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RastersListProcessingStatus Source # 
Read RastersListProcessingStatus Source # 
Show RastersListProcessingStatus Source # 
Generic RastersListProcessingStatus Source # 
Hashable RastersListProcessingStatus Source # 
ToJSON RastersListProcessingStatus Source # 
FromJSON RastersListProcessingStatus Source # 
FromHttpApiData RastersListProcessingStatus Source # 
ToHttpApiData RastersListProcessingStatus Source # 
type Rep RastersListProcessingStatus Source # 
type Rep RastersListProcessingStatus = D1 (MetaData "RastersListProcessingStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "RLPSComplete" PrefixI False) U1) (C1 (MetaCons "RLPSFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RLPSNotReady" PrefixI False) U1) ((:+:) (C1 (MetaCons "RLPSProcessing" PrefixI False) U1) (C1 (MetaCons "RLPSReady" PrefixI False) U1))))

Project

data Project Source #

A Maps Engine project groups a collection of resources.

See: project smart constructor.

Instances

Eq Project Source # 

Methods

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

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

Data Project Source # 

Methods

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

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

toConstr :: Project -> Constr #

dataTypeOf :: Project -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Project Source # 
Generic Project Source # 

Associated Types

type Rep Project :: * -> * #

Methods

from :: Project -> Rep Project x #

to :: Rep Project x -> Project #

ToJSON Project Source # 
FromJSON Project Source # 
type Rep Project Source # 
type Rep Project = D1 (MetaData "Project" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Project'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_proName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_proId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

project :: Project Source #

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

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

proName :: Lens' Project (Maybe Text) Source #

A user provided name for this Maps Engine project.

proId :: Lens' Project (Maybe Text) Source #

An ID used to refer to this Maps Engine project.

Color

data Color Source #

Basic color used in styling.

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 # 
type Rep Color = D1 (MetaData "Color" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Color'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cOpacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))))

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:

cColor :: Lens' Color (Maybe Text) Source #

The CSS style color, can be in format of "red" or "#7733EE".

cOpacity :: Lens' Color (Maybe Double) Source #

Opacity ranges from 0 to 1, inclusive. If not provided, default to 1.

LayersListProcessingStatus

data LayersListProcessingStatus Source #

Constructors

LLPSComplete

complete The layer has completed processing.

LLPSFailed

failed The layer has failed processing.

LLPSNotReady

notReady The layer is not ready for processing.

LLPSProcessing

processing The layer is processing.

LLPSReady

ready The layer is ready for processing.

Instances

Enum LayersListProcessingStatus Source # 
Eq LayersListProcessingStatus Source # 
Data LayersListProcessingStatus Source # 

Methods

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

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

toConstr :: LayersListProcessingStatus -> Constr #

dataTypeOf :: LayersListProcessingStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LayersListProcessingStatus Source # 
Read LayersListProcessingStatus Source # 
Show LayersListProcessingStatus Source # 
Generic LayersListProcessingStatus Source # 
Hashable LayersListProcessingStatus Source # 
ToJSON LayersListProcessingStatus Source # 
FromJSON LayersListProcessingStatus Source # 
FromHttpApiData LayersListProcessingStatus Source # 
ToHttpApiData LayersListProcessingStatus Source # 
type Rep LayersListProcessingStatus Source # 
type Rep LayersListProcessingStatus = D1 (MetaData "LayersListProcessingStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "LLPSComplete" PrefixI False) U1) (C1 (MetaCons "LLPSFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LLPSNotReady" PrefixI False) U1) ((:+:) (C1 (MetaCons "LLPSProcessing" PrefixI False) U1) (C1 (MetaCons "LLPSReady" PrefixI False) U1))))

RasterCollection

data RasterCollection Source #

A raster collection groups multiple Raster resources for inclusion in a Layer.

See: rasterCollection smart constructor.

Instances

Eq RasterCollection Source # 
Data RasterCollection Source # 

Methods

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

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

toConstr :: RasterCollection -> Constr #

dataTypeOf :: RasterCollection -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RasterCollection Source # 
Generic RasterCollection Source # 
ToJSON RasterCollection Source # 
FromJSON RasterCollection Source # 
type Rep RasterCollection Source # 
type Rep RasterCollection = D1 (MetaData "RasterCollection" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "RasterCollection'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_rcWritersCanEditPermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_rcEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rcCreatorEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcRasterType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RasterCollectionRasterType))) (S1 (MetaSel (Just Symbol "_rcLastModifiedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')))) ((:*:) (S1 (MetaSel (Just Symbol "_rcLastModifierEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rcName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcBbox") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Double]))) (S1 (MetaSel (Just Symbol "_rcProcessingStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RasterCollectionProcessingStatus)))) ((:*:) (S1 (MetaSel (Just Symbol "_rcMosaic") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_rcId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcProjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rcDraftAccessList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rcDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rcAttribution") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rcTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))))))))

rcCreationTime :: Lens' RasterCollection (Maybe UTCTime) Source #

The creation time of this RasterCollection. The value is an RFC 3339 formatted date-time value (e.g. 1970-01-01T00:00:00Z).

rcWritersCanEditPermissions :: Lens' RasterCollection (Maybe Bool) Source #

If true, WRITERs of the asset are able to edit the asset permissions.

rcEtag :: Lens' RasterCollection (Maybe Text) Source #

The ETag, used to refer to the current version of the asset.

rcCreatorEmail :: Lens' RasterCollection (Maybe Text) Source #

The email address of the creator of this raster collection. This is only returned on GET requests and not LIST requests.

rcRasterType :: Lens' RasterCollection (Maybe RasterCollectionRasterType) Source #

The type of rasters contained within this RasterCollection.

rcLastModifiedTime :: Lens' RasterCollection (Maybe UTCTime) Source #

The last modified time of this RasterCollection. The value is an RFC 3339 formatted date-time value (e.g. 1970-01-01T00:00:00Z).

rcLastModifierEmail :: Lens' RasterCollection (Maybe Text) Source #

The email address of the last modifier of this raster collection. This is only returned on GET requests and not LIST requests.

rcName :: Lens' RasterCollection (Maybe Text) Source #

The name of this RasterCollection, supplied by the author.

rcBbox :: Lens' RasterCollection [Double] Source #

A rectangular bounding box which contains all of the data in this RasterCollection. The box is expressed as \"west, south, east, north\". The numbers represent latitude and longitude in decimal degrees.

rcProcessingStatus :: Lens' RasterCollection (Maybe RasterCollectionProcessingStatus) Source #

The processing status of this RasterCollection.

rcMosaic :: Lens' RasterCollection (Maybe Bool) Source #

True if this RasterCollection is a mosaic.

rcId :: Lens' RasterCollection (Maybe Text) Source #

A globally unique ID, used to refer to this RasterCollection.

rcProjectId :: Lens' RasterCollection (Maybe Text) Source #

The ID of the project that this RasterCollection is in.

rcDraftAccessList :: Lens' RasterCollection (Maybe Text) Source #

Deprecated: The name of an access list of the Map Editor type. The user on whose behalf the request is being sent must be an editor on that access list. Note: Google Maps Engine no longer uses access lists. Instead, each asset has its own list of permissions. For backward compatibility, the API still accepts access lists for projects that are already using access lists. If you created a GME account/project after July 14th, 2014, you will not be able to send API requests that include access lists. Note: This is an input field only. It is not returned in response to a list or get request.

rcDescription :: Lens' RasterCollection (Maybe Text) Source #

The description of this RasterCollection, supplied by the author.

rcAttribution :: Lens' RasterCollection (Maybe Text) Source #

The name of the attribution to be used for this RasterCollection. Note: Attribution is returned in response to a get request but not a list request. After requesting a list of raster collections, you'll need to send a get request to retrieve the attribution for each raster collection.

rcTags :: Lens' RasterCollection [Text] Source #

Tags of this RasterCollection.

LineStyleStroke

data LineStyleStroke Source #

Stroke of the line.

See: lineStyleStroke smart constructor.

Instances

Eq LineStyleStroke Source # 
Data LineStyleStroke Source # 

Methods

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

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

toConstr :: LineStyleStroke -> Constr #

dataTypeOf :: LineStyleStroke -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LineStyleStroke Source # 
Generic LineStyleStroke Source # 
ToJSON LineStyleStroke Source # 
FromJSON LineStyleStroke Source # 
type Rep LineStyleStroke Source # 
type Rep LineStyleStroke = D1 (MetaData "LineStyleStroke" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "LineStyleStroke'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_lssColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_lssWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_lssOpacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))))))

lineStyleStroke :: LineStyleStroke Source #

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

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

lssWidth :: Lens' LineStyleStroke (Maybe Double) Source #

Width of the line, in pixels. 0 <= width <= 10. If width is set to 0, the line will be invisible.

RasterCollectionsRastersListRole

data RasterCollectionsRastersListRole Source #

The role parameter indicates that the response should only contain assets where the current user has the specified level of access.

Constructors

RCRLROwner

owner The user can read, write and administer the asset.

RCRLRReader

reader The user can read the asset.

RCRLRWriter

writer The user can read and write the asset.

Instances

Enum RasterCollectionsRastersListRole Source # 
Eq RasterCollectionsRastersListRole Source # 
Data RasterCollectionsRastersListRole Source # 

Methods

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

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

toConstr :: RasterCollectionsRastersListRole -> Constr #

dataTypeOf :: RasterCollectionsRastersListRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord RasterCollectionsRastersListRole Source # 
Read RasterCollectionsRastersListRole Source # 
Show RasterCollectionsRastersListRole Source # 
Generic RasterCollectionsRastersListRole Source # 
Hashable RasterCollectionsRastersListRole Source # 
ToJSON RasterCollectionsRastersListRole Source # 
FromJSON RasterCollectionsRastersListRole Source # 
FromHttpApiData RasterCollectionsRastersListRole Source # 
ToHttpApiData RasterCollectionsRastersListRole Source # 
type Rep RasterCollectionsRastersListRole Source # 
type Rep RasterCollectionsRastersListRole = D1 (MetaData "RasterCollectionsRastersListRole" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "RCRLROwner" PrefixI False) U1) ((:+:) (C1 (MetaCons "RCRLRReader" PrefixI False) U1) (C1 (MetaCons "RCRLRWriter" PrefixI False) U1)))

GeoJSONMultiPolygonType

data GeoJSONMultiPolygonType Source #

Identifies this object as a GeoJsonMultiPolygon.

Constructors

MultiPolygon
MultiPolygon

Instances

Enum GeoJSONMultiPolygonType Source # 
Eq GeoJSONMultiPolygonType Source # 
Data GeoJSONMultiPolygonType Source # 

Methods

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

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

toConstr :: GeoJSONMultiPolygonType -> Constr #

dataTypeOf :: GeoJSONMultiPolygonType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GeoJSONMultiPolygonType Source # 
Read GeoJSONMultiPolygonType Source # 
Show GeoJSONMultiPolygonType Source # 
Generic GeoJSONMultiPolygonType Source # 
Hashable GeoJSONMultiPolygonType Source # 
ToJSON GeoJSONMultiPolygonType Source # 
FromJSON GeoJSONMultiPolygonType Source # 
FromHttpApiData GeoJSONMultiPolygonType Source # 
ToHttpApiData GeoJSONMultiPolygonType Source # 
type Rep GeoJSONMultiPolygonType Source # 
type Rep GeoJSONMultiPolygonType = D1 (MetaData "GeoJSONMultiPolygonType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "MultiPolygon" PrefixI False) U1)

GeoJSONMultiPointType

data GeoJSONMultiPointType Source #

Identifies this object as a GeoJsonMultiPoint.

Constructors

MultiPoint
MultiPoint

Instances

Enum GeoJSONMultiPointType Source # 
Eq GeoJSONMultiPointType Source # 
Data GeoJSONMultiPointType Source # 

Methods

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

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

toConstr :: GeoJSONMultiPointType -> Constr #

dataTypeOf :: GeoJSONMultiPointType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GeoJSONMultiPointType Source # 
Read GeoJSONMultiPointType Source # 
Show GeoJSONMultiPointType Source # 
Generic GeoJSONMultiPointType Source # 
Hashable GeoJSONMultiPointType Source # 
ToJSON GeoJSONMultiPointType Source # 
FromJSON GeoJSONMultiPointType Source # 
FromHttpApiData GeoJSONMultiPointType Source # 
ToHttpApiData GeoJSONMultiPointType Source # 
type Rep GeoJSONMultiPointType Source # 
type Rep GeoJSONMultiPointType = D1 (MetaData "GeoJSONMultiPointType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "MultiPoint" PrefixI False) U1)

RasterCollectionsRastersBatchDeleteResponse

data RasterCollectionsRastersBatchDeleteResponse Source #

The response returned by a call to rasterCollections.rasters.batchDelete.

See: rasterCollectionsRastersBatchDeleteResponse smart constructor.

Instances

Eq RasterCollectionsRastersBatchDeleteResponse Source # 
Data RasterCollectionsRastersBatchDeleteResponse Source # 

Methods

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

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

toConstr :: RasterCollectionsRastersBatchDeleteResponse -> Constr #

dataTypeOf :: RasterCollectionsRastersBatchDeleteResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RasterCollectionsRastersBatchDeleteResponse Source # 
Generic RasterCollectionsRastersBatchDeleteResponse Source # 
ToJSON RasterCollectionsRastersBatchDeleteResponse Source # 
FromJSON RasterCollectionsRastersBatchDeleteResponse Source # 
type Rep RasterCollectionsRastersBatchDeleteResponse Source # 
type Rep RasterCollectionsRastersBatchDeleteResponse = D1 (MetaData "RasterCollectionsRastersBatchDeleteResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "RasterCollectionsRastersBatchDeleteResponse'" PrefixI False) U1)

ProcessResponse

data ProcessResponse Source #

The response returned by a call to any asset's Process method.

See: processResponse smart constructor.

Instances

Eq ProcessResponse Source # 
Data ProcessResponse Source # 

Methods

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

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

toConstr :: ProcessResponse -> Constr #

dataTypeOf :: ProcessResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ProcessResponse Source # 
Generic ProcessResponse Source # 
ToJSON ProcessResponse Source # 
FromJSON ProcessResponse Source # 
type Rep ProcessResponse Source # 
type Rep ProcessResponse = D1 (MetaData "ProcessResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "ProcessResponse'" PrefixI False) U1)

processResponse :: ProcessResponse Source #

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

TableColumn

data TableColumn Source #

Instances

Eq TableColumn Source # 
Data TableColumn Source # 

Methods

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

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

toConstr :: TableColumn -> Constr #

dataTypeOf :: TableColumn -> DataType #

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

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

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

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

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

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

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

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

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

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

Show TableColumn Source # 
Generic TableColumn Source # 

Associated Types

type Rep TableColumn :: * -> * #

ToJSON TableColumn Source # 
FromJSON TableColumn Source # 
type Rep TableColumn Source # 
type Rep TableColumn = D1 (MetaData "TableColumn" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "TableColumn'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tcName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tcType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TableColumnType)))))

tableColumn :: TableColumn Source #

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

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

tcName :: Lens' TableColumn (Maybe Text) Source #

The column name.

tcType :: Lens' TableColumn (Maybe TableColumnType) Source #

The type of data stored in this column.

PublishedLayerLayerType

data PublishedLayerLayerType Source #

The type of the datasources used to build this Layer. This should be used instead of datasourceType. At least one of layerType and datasourceType and must be specified, but layerType takes precedence.

Constructors

Image
image
Vector
vector

Instances

Enum PublishedLayerLayerType Source # 
Eq PublishedLayerLayerType Source # 
Data PublishedLayerLayerType Source # 

Methods

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

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

toConstr :: PublishedLayerLayerType -> Constr #

dataTypeOf :: PublishedLayerLayerType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PublishedLayerLayerType Source # 
Read PublishedLayerLayerType Source # 
Show PublishedLayerLayerType Source # 
Generic PublishedLayerLayerType Source # 
Hashable PublishedLayerLayerType Source # 
ToJSON PublishedLayerLayerType Source # 
FromJSON PublishedLayerLayerType Source # 
FromHttpApiData PublishedLayerLayerType Source # 
ToHttpApiData PublishedLayerLayerType Source # 
type Rep PublishedLayerLayerType Source # 
type Rep PublishedLayerLayerType = D1 (MetaData "PublishedLayerLayerType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "Image" PrefixI False) U1) (C1 (MetaCons "Vector" PrefixI False) U1))

TablesListProcessingStatus

data TablesListProcessingStatus Source #

Constructors

TLPSComplete

complete The table has completed processing.

TLPSFailed

failed The table has failed processing.

TLPSNotReady

notReady The table is not ready for processing.

TLPSProcessing

processing The table is processing.

TLPSReady

ready The table is ready for processing.

Instances

Enum TablesListProcessingStatus Source # 
Eq TablesListProcessingStatus Source # 
Data TablesListProcessingStatus Source # 

Methods

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

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

toConstr :: TablesListProcessingStatus -> Constr #

dataTypeOf :: TablesListProcessingStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TablesListProcessingStatus Source # 
Read TablesListProcessingStatus Source # 
Show TablesListProcessingStatus Source # 
Generic TablesListProcessingStatus Source # 
Hashable TablesListProcessingStatus Source # 
ToJSON TablesListProcessingStatus Source # 
FromJSON TablesListProcessingStatus Source # 
FromHttpApiData TablesListProcessingStatus Source # 
ToHttpApiData TablesListProcessingStatus Source # 
type Rep TablesListProcessingStatus Source # 
type Rep TablesListProcessingStatus = D1 (MetaData "TablesListProcessingStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "TLPSComplete" PrefixI False) U1) (C1 (MetaCons "TLPSFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TLPSNotReady" PrefixI False) U1) ((:+:) (C1 (MetaCons "TLPSProcessing" PrefixI False) U1) (C1 (MetaCons "TLPSReady" PrefixI False) U1))))

Asset

data Asset Source #

An asset is any Google Maps Engine resource that has a globally unique ID. Assets include maps, layers, vector tables, raster collections, and rasters. Projects and features are not considered assets. More detailed information about an asset can be obtained by querying the asset's particular endpoint.

See: asset smart constructor.

Instances

Eq Asset Source # 

Methods

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

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

Data Asset Source # 

Methods

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

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

toConstr :: Asset -> Constr #

dataTypeOf :: Asset -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Asset Source # 

Methods

showsPrec :: Int -> Asset -> ShowS #

show :: Asset -> String #

showList :: [Asset] -> ShowS #

Generic Asset Source # 

Associated Types

type Rep Asset :: * -> * #

Methods

from :: Asset -> Rep Asset x #

to :: Rep Asset x -> Asset #

ToJSON Asset Source # 
FromJSON Asset Source # 
type Rep Asset Source # 
type Rep Asset = D1 (MetaData "Asset" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Asset'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) ((:*:) (S1 (MetaSel (Just Symbol "_aWritersCanEditPermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))) (S1 (MetaSel (Just Symbol "_aEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aCreatorEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aLastModifiedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime')))) ((:*:) (S1 (MetaSel (Just Symbol "_aLastModifierEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aBbox") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Double]))) ((:*:) (S1 (MetaSel (Just Symbol "_aResource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_aProjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AssetType)))) ((:*:) (S1 (MetaSel (Just Symbol "_aDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_aTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))))))))

asset :: Asset Source #

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

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

aCreationTime :: Lens' Asset (Maybe UTCTime) Source #

The creation time of this asset. The value is an RFC 3339-formatted date-time value (for example, 1970-01-01T00:00:00Z).

aWritersCanEditPermissions :: Lens' Asset (Maybe Bool) Source #

If true, WRITERs of the asset are able to edit the asset permissions.

aEtag :: Lens' Asset (Maybe Text) Source #

The ETag, used to refer to the current version of the asset.

aCreatorEmail :: Lens' Asset (Maybe Text) Source #

The email address of the creator of this asset. This is only returned on GET requests and not LIST requests.

aLastModifiedTime :: Lens' Asset (Maybe UTCTime) Source #

The last modified time of this asset. The value is an RFC 3339-formatted date-time value (for example, 1970-01-01T00:00:00Z).

aLastModifierEmail :: Lens' Asset (Maybe Text) Source #

The email address of the last modifier of this asset. This is only returned on GET requests and not LIST requests.

aName :: Lens' Asset (Maybe Text) Source #

The asset's name.

aBbox :: Lens' Asset [Double] Source #

A rectangular bounding box which contains all of the data in this asset. The box is expressed as \"west, south, east, north\". The numbers represent latitude and longitude in decimal degrees.

aResource :: Lens' Asset (Maybe Text) Source #

The URL to query to retrieve the asset's complete object. The assets endpoint only returns high-level information about a resource.

aId :: Lens' Asset (Maybe Text) Source #

The asset's globally unique ID.

aProjectId :: Lens' Asset (Maybe Text) Source #

The ID of the project to which the asset belongs.

aType :: Lens' Asset (Maybe AssetType) Source #

The type of asset. One of raster, rasterCollection, table, map, or layer.

aDescription :: Lens' Asset (Maybe Text) Source #

The asset's description.

aTags :: Lens' Asset [Text] Source #

An array of text strings, with each string representing a tag. More information about tags can be found in the Tagging data article of the Maps Engine help center.

LayerLayerType

data LayerLayerType Source #

The type of the datasources used to build this Layer. This should be used instead of datasourceType. At least one of layerType and datasourceType and must be specified, but layerType takes precedence.

Constructors

LLTImage
image
LLTVector
vector

Instances

Enum LayerLayerType Source # 
Eq LayerLayerType Source # 
Data LayerLayerType Source # 

Methods

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

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

toConstr :: LayerLayerType -> Constr #

dataTypeOf :: LayerLayerType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LayerLayerType Source # 
Read LayerLayerType Source # 
Show LayerLayerType Source # 
Generic LayerLayerType Source # 

Associated Types

type Rep LayerLayerType :: * -> * #

Hashable LayerLayerType Source # 
ToJSON LayerLayerType Source # 
FromJSON LayerLayerType Source # 
FromHttpApiData LayerLayerType Source # 
ToHttpApiData LayerLayerType Source # 
type Rep LayerLayerType Source # 
type Rep LayerLayerType = D1 (MetaData "LayerLayerType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "LLTImage" PrefixI False) U1) (C1 (MetaCons "LLTVector" PrefixI False) U1))

ScaledShape

data ScaledShape Source #

Parameters for styling points as scaled shapes.

See: scaledShape smart constructor.

Instances

Eq ScaledShape Source # 
Data ScaledShape Source # 

Methods

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

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

toConstr :: ScaledShape -> Constr #

dataTypeOf :: ScaledShape -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ScaledShape Source # 
Generic ScaledShape Source # 

Associated Types

type Rep ScaledShape :: * -> * #

ToJSON ScaledShape Source # 
FromJSON ScaledShape Source # 
type Rep ScaledShape Source # 
type Rep ScaledShape = D1 (MetaData "ScaledShape" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "ScaledShape'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ssBOrder") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BOrder))) ((:*:) (S1 (MetaSel (Just Symbol "_ssFill") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Color))) (S1 (MetaSel (Just Symbol "_ssShape") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ScaledShapeShape))))))

scaledShape :: ScaledShape Source #

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

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

ssBOrder :: Lens' ScaledShape (Maybe BOrder) Source #

Border color/width of the shape. If not specified the shape won't have a border.

ssFill :: Lens' ScaledShape (Maybe Color) Source #

The fill color of the shape. If not specified the shape will be transparent (although the borders may not be).

PermissionType

data PermissionType Source #

The account type.

Constructors

Anyone
anyone
Group
group
User
user

Instances

Enum PermissionType Source # 
Eq PermissionType Source # 
Data PermissionType Source # 

Methods

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

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

toConstr :: PermissionType -> Constr #

dataTypeOf :: PermissionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord PermissionType Source # 
Read PermissionType Source # 
Show PermissionType Source # 
Generic PermissionType Source # 

Associated Types

type Rep PermissionType :: * -> * #

Hashable PermissionType Source # 
ToJSON PermissionType Source # 
FromJSON PermissionType Source # 
FromHttpApiData PermissionType Source # 
ToHttpApiData PermissionType Source # 
type Rep PermissionType Source # 
type Rep PermissionType = D1 (MetaData "PermissionType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "Anyone" PrefixI False) U1) ((:+:) (C1 (MetaCons "Group" PrefixI False) U1) (C1 (MetaCons "User" PrefixI False) U1)))

MapProcessingStatus

data MapProcessingStatus Source #

The processing status of this map. Map processing is automatically started once a map becomes ready for processing.

Constructors

MPSComplete
complete
MPSFailed
failed
MPSNotReady
notReady
MPSProcessing
processing
MPSReady
ready

Instances

Enum MapProcessingStatus Source # 
Eq MapProcessingStatus Source # 
Data MapProcessingStatus Source # 

Methods

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

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

toConstr :: MapProcessingStatus -> Constr #

dataTypeOf :: MapProcessingStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MapProcessingStatus Source # 
Read MapProcessingStatus Source # 
Show MapProcessingStatus Source # 
Generic MapProcessingStatus Source # 
Hashable MapProcessingStatus Source # 
ToJSON MapProcessingStatus Source # 
FromJSON MapProcessingStatus Source # 
FromHttpApiData MapProcessingStatus Source # 
ToHttpApiData MapProcessingStatus Source # 
type Rep MapProcessingStatus Source # 
type Rep MapProcessingStatus = D1 (MetaData "MapProcessingStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "MPSComplete" PrefixI False) U1) (C1 (MetaCons "MPSFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MPSNotReady" PrefixI False) U1) ((:+:) (C1 (MetaCons "MPSProcessing" PrefixI False) U1) (C1 (MetaCons "MPSReady" PrefixI False) U1))))

FeaturesBatchDeleteRequest

data FeaturesBatchDeleteRequest Source #

The request sent to features.BatchDelete.

See: featuresBatchDeleteRequest smart constructor.

Instances

Eq FeaturesBatchDeleteRequest Source # 
Data FeaturesBatchDeleteRequest Source # 

Methods

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

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

toConstr :: FeaturesBatchDeleteRequest -> Constr #

dataTypeOf :: FeaturesBatchDeleteRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FeaturesBatchDeleteRequest Source # 
Generic FeaturesBatchDeleteRequest Source # 
ToJSON FeaturesBatchDeleteRequest Source # 
FromJSON FeaturesBatchDeleteRequest Source # 
type Rep FeaturesBatchDeleteRequest Source # 
type Rep FeaturesBatchDeleteRequest = D1 (MetaData "FeaturesBatchDeleteRequest" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "FeaturesBatchDeleteRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fbdrPrimaryKeys") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_fbdrGxIds") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))))

featuresBatchDeleteRequest :: FeaturesBatchDeleteRequest Source #

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

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

MapsGetVersion

data MapsGetVersion Source #

Deprecated: The version parameter indicates which version of the map should be returned. When version is set to published, the published version of the map will be returned. Please use the maps.getPublished endpoint instead.

Constructors

Draft

draft The draft version.

Published

published The published version.

Instances

Enum MapsGetVersion Source # 
Eq MapsGetVersion Source # 
Data MapsGetVersion Source # 

Methods

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

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

toConstr :: MapsGetVersion -> Constr #

dataTypeOf :: MapsGetVersion -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MapsGetVersion Source # 
Read MapsGetVersion Source # 
Show MapsGetVersion Source # 
Generic MapsGetVersion Source # 

Associated Types

type Rep MapsGetVersion :: * -> * #

Hashable MapsGetVersion Source # 
ToJSON MapsGetVersion Source # 
FromJSON MapsGetVersion Source # 
FromHttpApiData MapsGetVersion Source # 
ToHttpApiData MapsGetVersion Source # 
type Rep MapsGetVersion Source # 
type Rep MapsGetVersion = D1 (MetaData "MapsGetVersion" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "Draft" PrefixI False) U1) (C1 (MetaCons "Published" PrefixI False) U1))

TablesListRole

data TablesListRole Source #

The role parameter indicates that the response should only contain assets where the current user has the specified level of access.

Constructors

TLROwner

owner The user can read, write and administer the asset.

TLRReader

reader The user can read the asset.

TLRWriter

writer The user can read and write the asset.

Instances

Enum TablesListRole Source # 
Eq TablesListRole Source # 
Data TablesListRole Source # 

Methods

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

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

toConstr :: TablesListRole -> Constr #

dataTypeOf :: TablesListRole -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TablesListRole Source # 
Read TablesListRole Source # 
Show TablesListRole Source # 
Generic TablesListRole Source # 

Associated Types

type Rep TablesListRole :: * -> * #

Hashable TablesListRole Source # 
ToJSON TablesListRole Source # 
FromJSON TablesListRole Source # 
FromHttpApiData TablesListRole Source # 
ToHttpApiData TablesListRole Source # 
type Rep TablesListRole Source # 
type Rep TablesListRole = D1 (MetaData "TablesListRole" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "TLROwner" PrefixI False) U1) ((:+:) (C1 (MetaCons "TLRReader" PrefixI False) U1) (C1 (MetaCons "TLRWriter" PrefixI False) U1)))

Icon

data Icon Source #

An icon is a user-uploaded image that can be used to style point geometries.

See: icon smart constructor.

Instances

Eq Icon Source # 

Methods

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

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

Data Icon Source # 

Methods

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

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

toConstr :: Icon -> Constr #

dataTypeOf :: Icon -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Icon Source # 

Methods

showsPrec :: Int -> Icon -> ShowS #

show :: Icon -> String #

showList :: [Icon] -> ShowS #

Generic Icon Source # 

Associated Types

type Rep Icon :: * -> * #

Methods

from :: Icon -> Rep Icon x #

to :: Rep Icon x -> Icon #

ToJSON Icon Source # 
FromJSON Icon Source # 
type Rep Icon Source # 
type Rep Icon = D1 (MetaData "Icon" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Icon'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_iName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_iId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_iDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

icon :: Icon Source #

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

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

iName :: Lens' Icon (Maybe Text) Source #

The name of this Icon, supplied by the author.

iId :: Lens' Icon (Maybe Text) Source #

An ID used to refer to this Icon.

iDescription :: Lens' Icon (Maybe Text) Source #

The description of this Icon, supplied by the author.

VectorStyleType

data VectorStyleType Source #

The type of the vector style. Currently, only displayRule is supported.

Constructors

VSTDisplayRule
displayRule

Instances

Enum VectorStyleType Source # 
Eq VectorStyleType Source # 
Data VectorStyleType Source # 

Methods

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

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

toConstr :: VectorStyleType -> Constr #

dataTypeOf :: VectorStyleType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord VectorStyleType Source # 
Read VectorStyleType Source # 
Show VectorStyleType Source # 
Generic VectorStyleType Source # 
Hashable VectorStyleType Source # 
ToJSON VectorStyleType Source # 
FromJSON VectorStyleType Source # 
FromHttpApiData VectorStyleType Source # 
ToHttpApiData VectorStyleType Source # 
type Rep VectorStyleType Source # 
type Rep VectorStyleType = D1 (MetaData "VectorStyleType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "VSTDisplayRule" PrefixI False) U1)

GeoJSONLineStringType

data GeoJSONLineStringType Source #

Identifies this object as a GeoJsonLineString.

Constructors

LineString
LineString

Instances

Enum GeoJSONLineStringType Source # 
Eq GeoJSONLineStringType Source # 
Data GeoJSONLineStringType Source # 

Methods

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

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

toConstr :: GeoJSONLineStringType -> Constr #

dataTypeOf :: GeoJSONLineStringType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GeoJSONLineStringType Source # 
Read GeoJSONLineStringType Source # 
Show GeoJSONLineStringType Source # 
Generic GeoJSONLineStringType Source # 
Hashable GeoJSONLineStringType Source # 
ToJSON GeoJSONLineStringType Source # 
FromJSON GeoJSONLineStringType Source # 
FromHttpApiData GeoJSONLineStringType Source # 
ToHttpApiData GeoJSONLineStringType Source # 
type Rep GeoJSONLineStringType Source # 
type Rep GeoJSONLineStringType = D1 (MetaData "GeoJSONLineStringType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "LineString" PrefixI False) U1)

ParentsListResponse

data ParentsListResponse Source #

The response returned by a call to parents.List.

See: parentsListResponse smart constructor.

Instances

Eq ParentsListResponse Source # 
Data ParentsListResponse Source # 

Methods

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

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

toConstr :: ParentsListResponse -> Constr #

dataTypeOf :: ParentsListResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ParentsListResponse Source # 
Generic ParentsListResponse Source # 
ToJSON ParentsListResponse Source # 
FromJSON ParentsListResponse Source # 
type Rep ParentsListResponse Source # 
type Rep ParentsListResponse = D1 (MetaData "ParentsListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "ParentsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_plrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_plrParents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Parent])))))

parentsListResponse :: ParentsListResponse Source #

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

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

FeaturesListResponse

data FeaturesListResponse Source #

The response returned by a call to features.List.

See: featuresListResponse smart constructor.

Instances

Eq FeaturesListResponse Source # 
Data FeaturesListResponse Source # 

Methods

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

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

toConstr :: FeaturesListResponse -> Constr #

dataTypeOf :: FeaturesListResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FeaturesListResponse Source # 
Generic FeaturesListResponse Source # 
ToJSON FeaturesListResponse Source # 
FromJSON FeaturesListResponse Source # 
type Rep FeaturesListResponse Source # 
type Rep FeaturesListResponse = D1 (MetaData "FeaturesListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "FeaturesListResponse'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_flrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_flrAllowedQueriesPerSecond") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))) ((:*:) (S1 (MetaSel (Just Symbol "_flrSchema") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Schema))) ((:*:) (S1 (MetaSel (Just Symbol "_flrFeatures") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Feature]))) (S1 (MetaSel (Just Symbol "_flrType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))))

featuresListResponse :: FeaturesListResponse Source #

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

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

flrAllowedQueriesPerSecond :: Lens' FeaturesListResponse (Maybe Double) Source #

An indicator of the maximum rate at which queries may be made, if all queries were as expensive as this query.

RasterCollectionsRastersBatchInsertResponse

data RasterCollectionsRastersBatchInsertResponse Source #

The response returned by a call to rasterCollections.rasters.batchInsert.

See: rasterCollectionsRastersBatchInsertResponse smart constructor.

Instances

Eq RasterCollectionsRastersBatchInsertResponse Source # 
Data RasterCollectionsRastersBatchInsertResponse Source # 

Methods

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

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

toConstr :: RasterCollectionsRastersBatchInsertResponse -> Constr #

dataTypeOf :: RasterCollectionsRastersBatchInsertResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RasterCollectionsRastersBatchInsertResponse Source # 
Generic RasterCollectionsRastersBatchInsertResponse Source # 
ToJSON RasterCollectionsRastersBatchInsertResponse Source # 
FromJSON RasterCollectionsRastersBatchInsertResponse Source # 
type Rep RasterCollectionsRastersBatchInsertResponse Source # 
type Rep RasterCollectionsRastersBatchInsertResponse = D1 (MetaData "RasterCollectionsRastersBatchInsertResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "RasterCollectionsRastersBatchInsertResponse'" PrefixI False) U1)

LayerPublishingStatus

data LayerPublishingStatus Source #

The publishing status of this layer.

Constructors

LPSNotPublished
notPublished
LPSPublished
published

Instances

Enum LayerPublishingStatus Source # 
Eq LayerPublishingStatus Source # 
Data LayerPublishingStatus Source # 

Methods

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

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

toConstr :: LayerPublishingStatus -> Constr #

dataTypeOf :: LayerPublishingStatus -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LayerPublishingStatus Source # 
Read LayerPublishingStatus Source # 
Show LayerPublishingStatus Source # 
Generic LayerPublishingStatus Source # 
Hashable LayerPublishingStatus Source # 
ToJSON LayerPublishingStatus Source # 
FromJSON LayerPublishingStatus Source # 
FromHttpApiData LayerPublishingStatus Source # 
ToHttpApiData LayerPublishingStatus Source # 
type Rep LayerPublishingStatus Source # 
type Rep LayerPublishingStatus = D1 (MetaData "LayerPublishingStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "LPSNotPublished" PrefixI False) U1) (C1 (MetaCons "LPSPublished" PrefixI False) U1))

MapKmlLinkType

data MapKmlLinkType Source #

Identifies this object as a MapKmlLink.

Constructors

KmlLink
kmlLink

Instances

Enum MapKmlLinkType Source # 
Eq MapKmlLinkType Source # 
Data MapKmlLinkType Source # 

Methods

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

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

toConstr :: MapKmlLinkType -> Constr #

dataTypeOf :: MapKmlLinkType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord MapKmlLinkType Source # 
Read MapKmlLinkType Source # 
Show MapKmlLinkType Source # 
Generic MapKmlLinkType Source # 

Associated Types

type Rep MapKmlLinkType :: * -> * #

Hashable MapKmlLinkType Source # 
ToJSON MapKmlLinkType Source # 
FromJSON MapKmlLinkType Source # 
FromHttpApiData MapKmlLinkType Source # 
ToHttpApiData MapKmlLinkType Source # 
type Rep MapKmlLinkType Source # 
type Rep MapKmlLinkType = D1 (MetaData "MapKmlLinkType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "KmlLink" PrefixI False) U1)

LayerDatasourceType

data LayerDatasourceType Source #

Deprecated: The type of the datasources used to build this Layer. Note: This has been replaced by layerType, but is still available for now to maintain backward compatibility.

Constructors

LDTImage
image
LDTTable
table

Instances

Enum LayerDatasourceType Source # 
Eq LayerDatasourceType Source # 
Data LayerDatasourceType Source # 

Methods

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

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

toConstr :: LayerDatasourceType -> Constr #

dataTypeOf :: LayerDatasourceType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LayerDatasourceType Source # 
Read LayerDatasourceType Source # 
Show LayerDatasourceType Source # 
Generic LayerDatasourceType Source # 
Hashable LayerDatasourceType Source # 
ToJSON LayerDatasourceType Source # 
FromJSON LayerDatasourceType Source # 
FromHttpApiData LayerDatasourceType Source # 
ToHttpApiData LayerDatasourceType Source # 
type Rep LayerDatasourceType Source # 
type Rep LayerDatasourceType = D1 (MetaData "LayerDatasourceType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "LDTImage" PrefixI False) U1) (C1 (MetaCons "LDTTable" PrefixI False) U1))

GeoJSONGeometryCollectionType

data GeoJSONGeometryCollectionType Source #

Identifies this object as a GeoJsonGeometryCollection.

Constructors

GeometryCollection
GeometryCollection

Instances

Enum GeoJSONGeometryCollectionType Source # 
Eq GeoJSONGeometryCollectionType Source # 
Data GeoJSONGeometryCollectionType Source # 

Methods

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

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

toConstr :: GeoJSONGeometryCollectionType -> Constr #

dataTypeOf :: GeoJSONGeometryCollectionType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GeoJSONGeometryCollectionType Source # 
Read GeoJSONGeometryCollectionType Source # 
Show GeoJSONGeometryCollectionType Source # 
Generic GeoJSONGeometryCollectionType Source # 
Hashable GeoJSONGeometryCollectionType Source # 
ToJSON GeoJSONGeometryCollectionType Source # 
FromJSON GeoJSONGeometryCollectionType Source # 
FromHttpApiData GeoJSONGeometryCollectionType Source # 
ToHttpApiData GeoJSONGeometryCollectionType Source # 
type Rep GeoJSONGeometryCollectionType Source # 
type Rep GeoJSONGeometryCollectionType = D1 (MetaData "GeoJSONGeometryCollectionType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "GeometryCollection" PrefixI False) U1)

IconsListResponse

data IconsListResponse Source #

The response returned by a call to icons.List.

See: iconsListResponse smart constructor.

Instances

Eq IconsListResponse Source # 
Data IconsListResponse Source # 

Methods

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

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

toConstr :: IconsListResponse -> Constr #

dataTypeOf :: IconsListResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show IconsListResponse Source # 
Generic IconsListResponse Source # 
ToJSON IconsListResponse Source # 
FromJSON IconsListResponse Source # 
type Rep IconsListResponse Source # 
type Rep IconsListResponse = D1 (MetaData "IconsListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "IconsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ilrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_ilrIcons") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Icon])))))

iconsListResponse :: IconsListResponse Source #

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

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

ilrIcons :: Lens' IconsListResponse [Icon] Source #

Resources returned.

LabelStyle

data LabelStyle Source #

Text label style.

See: labelStyle smart constructor.

Instances

Eq LabelStyle Source # 
Data LabelStyle Source # 

Methods

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

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

toConstr :: LabelStyle -> Constr #

dataTypeOf :: LabelStyle -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LabelStyle Source # 
Generic LabelStyle Source # 

Associated Types

type Rep LabelStyle :: * -> * #

ToJSON LabelStyle Source # 
FromJSON LabelStyle Source # 
type Rep LabelStyle Source # 

labelStyle :: LabelStyle Source #

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

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

lsFontStyle :: Lens' LabelStyle (Maybe LabelStyleFontStyle) Source #

Font style of the label, defaults to 'normal'.

lsColor :: Lens' LabelStyle (Maybe Text) Source #

Color of the text. If not provided, default to black.

lsSize :: Lens' LabelStyle (Maybe Double) Source #

Font size of the label, in pixels. 8 <= size <= 15. If not provided, a default size will be provided.

lsOpacity :: Lens' LabelStyle (Maybe Double) Source #

Opacity of the text.

lsOutline :: Lens' LabelStyle (Maybe Color) Source #

Outline color of the text.

lsFontWeight :: Lens' LabelStyle (Maybe LabelStyleFontWeight) Source #

Font weight of the label, defaults to 'normal'.

lsColumn :: Lens' LabelStyle (Maybe Text) Source #

The column value of the feature to be displayed.

RasterCollectionsRasterBatchDeleteRequest

data RasterCollectionsRasterBatchDeleteRequest Source #

The request sent to rasterCollections.Rasters.BatchDelete.

See: rasterCollectionsRasterBatchDeleteRequest smart constructor.

Instances

Eq RasterCollectionsRasterBatchDeleteRequest Source # 
Data RasterCollectionsRasterBatchDeleteRequest Source # 

Methods

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

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

toConstr :: RasterCollectionsRasterBatchDeleteRequest -> Constr #

dataTypeOf :: RasterCollectionsRasterBatchDeleteRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show RasterCollectionsRasterBatchDeleteRequest Source # 
Generic RasterCollectionsRasterBatchDeleteRequest Source # 
ToJSON RasterCollectionsRasterBatchDeleteRequest Source # 
FromJSON RasterCollectionsRasterBatchDeleteRequest Source # 
type Rep RasterCollectionsRasterBatchDeleteRequest Source # 
type Rep RasterCollectionsRasterBatchDeleteRequest = D1 (MetaData "RasterCollectionsRasterBatchDeleteRequest" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" True) (C1 (MetaCons "RasterCollectionsRasterBatchDeleteRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_rcrbdrIds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))))

rasterCollectionsRasterBatchDeleteRequest :: RasterCollectionsRasterBatchDeleteRequest Source #

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

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

rcrbdrIds :: Lens' RasterCollectionsRasterBatchDeleteRequest [Text] Source #

An array of Raster asset IDs to be removed from this RasterCollection.

Schema

data Schema Source #

A schema indicating the properties which may be associated with features within a Table, and the types of those properties.

See: schema smart constructor.

Instances

Eq Schema Source # 

Methods

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

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

Data Schema Source # 

Methods

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

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

toConstr :: Schema -> Constr #

dataTypeOf :: Schema -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Schema Source # 
Generic Schema Source # 

Associated Types

type Rep Schema :: * -> * #

Methods

from :: Schema -> Rep Schema x #

to :: Rep Schema x -> Schema #

ToJSON Schema Source # 
FromJSON Schema Source # 
type Rep Schema Source # 
type Rep Schema = D1 (MetaData "Schema" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Schema'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sPrimaryKey") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_sColumns") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [TableColumn]))) (S1 (MetaSel (Just Symbol "_sPrimaryGeometry") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

schema :: Schema Source #

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

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

sPrimaryKey :: Lens' Schema (Maybe Text) Source #

The name of the column that contains the unique identifier of a Feature.

sColumns :: Lens' Schema [TableColumn] Source #

An array of TableColumn objects. The first object in the array must be named geometry and be of type points, lineStrings, polygons, or mixedGeometry.

sPrimaryGeometry :: Lens' Schema (Maybe Text) Source #

The name of the column that contains a feature's geometry. This field can be omitted during table create; Google Maps Engine supports only a single geometry column, which must be named geometry and be the first object in the columns array.

MapItem

data MapItem Source #

Instances

Eq MapItem Source # 

Methods

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

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

Data MapItem Source # 

Methods

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

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

toConstr :: MapItem -> Constr #

dataTypeOf :: MapItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show MapItem Source # 
Generic MapItem Source # 

Associated Types

type Rep MapItem :: * -> * #

Methods

from :: MapItem -> Rep MapItem x #

to :: Rep MapItem x -> MapItem #

ToJSON MapItem Source # 
FromJSON MapItem Source # 
type Rep MapItem Source # 
type Rep MapItem = D1 (MetaData "MapItem" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "MapItem'" PrefixI False) U1)

mapItem :: MapItem Source #

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

GeoJSONPointType

data GeoJSONPointType Source #

Identifies this object as a GeoJsonPoint.

Constructors

Point
Point

Instances

Enum GeoJSONPointType Source # 
Eq GeoJSONPointType Source # 
Data GeoJSONPointType Source # 

Methods

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

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

toConstr :: GeoJSONPointType -> Constr #

dataTypeOf :: GeoJSONPointType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GeoJSONPointType Source # 
Read GeoJSONPointType Source # 
Show GeoJSONPointType Source # 
Generic GeoJSONPointType Source # 
Hashable GeoJSONPointType Source # 
ToJSON GeoJSONPointType Source # 
FromJSON GeoJSONPointType Source # 
FromHttpApiData GeoJSONPointType Source # 
ToHttpApiData GeoJSONPointType Source # 
type Rep GeoJSONPointType Source # 
type Rep GeoJSONPointType = D1 (MetaData "GeoJSONPointType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Point" PrefixI False) U1)

GeoJSONPolygonType

data GeoJSONPolygonType Source #

Identifies this object as a GeoJsonPolygon.

Constructors

Polygon
Polygon

Instances

Enum GeoJSONPolygonType Source # 
Eq GeoJSONPolygonType Source # 
Data GeoJSONPolygonType Source # 

Methods

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

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

toConstr :: GeoJSONPolygonType -> Constr #

dataTypeOf :: GeoJSONPolygonType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord GeoJSONPolygonType Source # 
Read GeoJSONPolygonType Source # 
Show GeoJSONPolygonType Source # 
Generic GeoJSONPolygonType Source # 
Hashable GeoJSONPolygonType Source # 
ToJSON GeoJSONPolygonType Source # 
FromJSON GeoJSONPolygonType Source # 
FromHttpApiData GeoJSONPolygonType Source # 
ToHttpApiData GeoJSONPolygonType Source # 
type Rep GeoJSONPolygonType Source # 
type Rep GeoJSONPolygonType = D1 (MetaData "GeoJSONPolygonType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Polygon" PrefixI False) U1)

RasterCollectionsRastersBatchInsertRequest

data RasterCollectionsRastersBatchInsertRequest Source #

The request sent to rasterCollections.Rasters.BatchInsert.

See: rasterCollectionsRastersBatchInsertRequest smart constructor.

Instances

Eq RasterCollectionsRastersBatchInsertRequest Source # 
Data RasterCollectionsRastersBatchInsertRequest Source # 

Methods

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

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

toConstr :: RasterCollectionsRastersBatchInsertRequest -> Constr #

dataTypeOf :: RasterCollectionsRastersBatchInsertRequest -> DataType #

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

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

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

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

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

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

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

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RasterCollectionsRastersBatchInsertRequest -> m RasterCollectionsRastersBatchInsertRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionsRastersBatchInsertRequest -> m RasterCollectionsRastersBatchInsertRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionsRastersBatchInsertRequest -> m RasterCollectionsRastersBatchInsertRequest #

Show RasterCollectionsRastersBatchInsertRequest Source # 
Generic RasterCollectionsRastersBatchInsertRequest Source # 
ToJSON RasterCollectionsRastersBatchInsertRequest Source # 
FromJSON RasterCollectionsRastersBatchInsertRequest Source # 
type Rep RasterCollectionsRastersBatchInsertRequest Source # 
type Rep RasterCollectionsRastersBatchInsertRequest = D1 (MetaData "RasterCollectionsRastersBatchInsertRequest" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" True) (C1 (MetaCons "RasterCollectionsRastersBatchInsertRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_rcrbirIds") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Text]))))

rasterCollectionsRastersBatchInsertRequest :: RasterCollectionsRastersBatchInsertRequest Source #

Creates a value of RasterCollectionsRastersBatchInsertRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rcrbirIds :: Lens' RasterCollectionsRastersBatchInsertRequest [Text] Source #

An array of Raster asset IDs to be added to this RasterCollection.

PublishedMap

data PublishedMap Source #

The published version of a map asset.

See: publishedMap smart constructor.

Instances

Eq PublishedMap Source # 
Data PublishedMap Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PublishedMap -> c PublishedMap #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PublishedMap #

toConstr :: PublishedMap -> Constr #

dataTypeOf :: PublishedMap -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PublishedMap) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublishedMap) #

gmapT :: (forall b. Data b => b -> b) -> PublishedMap -> PublishedMap #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PublishedMap -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PublishedMap -> r #

gmapQ :: (forall d. Data d => d -> u) -> PublishedMap -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PublishedMap -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PublishedMap -> m PublishedMap #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PublishedMap -> m PublishedMap #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PublishedMap -> m PublishedMap #

Show PublishedMap Source # 
Generic PublishedMap Source # 

Associated Types

type Rep PublishedMap :: * -> * #

ToJSON PublishedMap Source # 
FromJSON PublishedMap Source # 
type Rep PublishedMap Source # 
type Rep PublishedMap = D1 (MetaData "PublishedMap" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "PublishedMap'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pmDefaultViewport") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Double]))) ((:*:) (S1 (MetaSel (Just Symbol "_pmContents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [MapItem]))) (S1 (MetaSel (Just Symbol "_pmName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) (S1 (MetaSel (Just Symbol "_pmId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_pmProjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pmDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

publishedMap :: PublishedMap Source #

Creates a value of PublishedMap with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pmDefaultViewport :: Lens' PublishedMap [Double] Source #

An array of four numbers (west, south, east, north) which defines the rectangular bounding box of the default viewport. The numbers represent latitude and longitude in decimal degrees.

pmContents :: Lens' PublishedMap [MapItem] Source #

The contents of this Map.

pmName :: Lens' PublishedMap (Maybe Text) Source #

The name of this Map, supplied by the author.

pmId :: Lens' PublishedMap (Maybe Text) Source #

A globally unique ID, used to refer to this Map.

pmProjectId :: Lens' PublishedMap (Maybe Text) Source #

The ID of the project that this Map is in.

pmDescription :: Lens' PublishedMap (Maybe Text) Source #

The description of this Map, supplied by the author.

AcquisitionTime

data AcquisitionTime Source #

Acquisition time represents acquired time of a raster.

See: acquisitionTime smart constructor.

Instances

Eq AcquisitionTime Source # 
Data AcquisitionTime Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AcquisitionTime -> c AcquisitionTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AcquisitionTime #

toConstr :: AcquisitionTime -> Constr #

dataTypeOf :: AcquisitionTime -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AcquisitionTime) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AcquisitionTime) #

gmapT :: (forall b. Data b => b -> b) -> AcquisitionTime -> AcquisitionTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AcquisitionTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AcquisitionTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> AcquisitionTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AcquisitionTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AcquisitionTime -> m AcquisitionTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AcquisitionTime -> m AcquisitionTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AcquisitionTime -> m AcquisitionTime #

Show AcquisitionTime Source # 
Generic AcquisitionTime Source # 
ToJSON AcquisitionTime Source # 
FromJSON AcquisitionTime Source # 
type Rep AcquisitionTime Source # 
type Rep AcquisitionTime = D1 (MetaData "AcquisitionTime" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "AcquisitionTime'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_atStart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) ((:*:) (S1 (MetaSel (Just Symbol "_atPrecision") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AcquisitionTimePrecision))) (S1 (MetaSel (Just Symbol "_atEnd") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))))))

acquisitionTime :: AcquisitionTime Source #

Creates a value of AcquisitionTime with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

atStart :: Lens' AcquisitionTime (Maybe UTCTime) Source #

The acquisition time, or start time if acquisition time is a range. The value is an RFC 3339 formatted date-time value (1970-01-01T00:00:00Z).

atPrecision :: Lens' AcquisitionTime (Maybe AcquisitionTimePrecision) Source #

The precision of acquisition time.

atEnd :: Lens' AcquisitionTime (Maybe UTCTime) Source #

The end time if acquisition time is a range. The value is an RFC 3339 formatted date-time value (1970-01-01T00:00:00Z).

LayersGetVersion

data LayersGetVersion Source #

Deprecated: The version parameter indicates which version of the layer should be returned. When version is set to published, the published version of the layer will be returned. Please use the layers.getPublished endpoint instead.

Constructors

LGVDraft

draft The draft version.

LGVPublished

published The published version.

Instances

Enum LayersGetVersion Source # 
Eq LayersGetVersion Source # 
Data LayersGetVersion Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LayersGetVersion -> c LayersGetVersion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LayersGetVersion #

toConstr :: LayersGetVersion -> Constr #

dataTypeOf :: LayersGetVersion -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LayersGetVersion) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LayersGetVersion) #

gmapT :: (forall b. Data b => b -> b) -> LayersGetVersion -> LayersGetVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LayersGetVersion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LayersGetVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> LayersGetVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LayersGetVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LayersGetVersion -> m LayersGetVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LayersGetVersion -> m LayersGetVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LayersGetVersion -> m LayersGetVersion #

Ord LayersGetVersion Source # 
Read LayersGetVersion Source # 
Show LayersGetVersion Source # 
Generic LayersGetVersion Source # 
Hashable LayersGetVersion Source # 
ToJSON LayersGetVersion Source # 
FromJSON LayersGetVersion Source # 
FromHttpApiData LayersGetVersion Source # 
ToHttpApiData LayersGetVersion Source # 
type Rep LayersGetVersion Source # 
type Rep LayersGetVersion = D1 (MetaData "LayersGetVersion" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "LGVDraft" PrefixI False) U1) (C1 (MetaCons "LGVPublished" PrefixI False) U1))

TablesListResponse

data TablesListResponse Source #

The response returned by a call to tables.List. Note: The list response does not include all the fields available in a table. Refer to the table resource description for details of the fields that are not included. You'll need to send a get request to retrieve the additional fields for each table.

See: tablesListResponse smart constructor.

Instances

Eq TablesListResponse Source # 
Data TablesListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TablesListResponse -> c TablesListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TablesListResponse #

toConstr :: TablesListResponse -> Constr #

dataTypeOf :: TablesListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TablesListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TablesListResponse) #

gmapT :: (forall b. Data b => b -> b) -> TablesListResponse -> TablesListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TablesListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TablesListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> TablesListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TablesListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TablesListResponse -> m TablesListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TablesListResponse -> m TablesListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TablesListResponse -> m TablesListResponse #

Show TablesListResponse Source # 
Generic TablesListResponse Source # 
ToJSON TablesListResponse Source # 
FromJSON TablesListResponse Source # 
type Rep TablesListResponse Source # 
type Rep TablesListResponse = D1 (MetaData "TablesListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "TablesListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_tlrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bytes))) (S1 (MetaSel (Just Symbol "_tlrTables") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Table])))))

tablesListResponse :: TablesListResponse Source #

Creates a value of TablesListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

IconStyle

data IconStyle Source #

Style for icon, this is part of point style.

See: iconStyle smart constructor.

Instances

Eq IconStyle Source # 
Data IconStyle Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> IconStyle -> c IconStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c IconStyle #

toConstr :: IconStyle -> Constr #

dataTypeOf :: IconStyle -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c IconStyle) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c IconStyle) #

gmapT :: (forall b. Data b => b -> b) -> IconStyle -> IconStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> IconStyle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> IconStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> IconStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> IconStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> IconStyle -> m IconStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> IconStyle -> m IconStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> IconStyle -> m IconStyle #

Show IconStyle Source # 
Generic IconStyle Source # 

Associated Types

type Rep IconStyle :: * -> * #

ToJSON IconStyle Source # 
FromJSON IconStyle Source # 
type Rep IconStyle Source # 
type Rep IconStyle = D1 (MetaData "IconStyle" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "IconStyle'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_isScaledShape") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ScaledShape))) (S1 (MetaSel (Just Symbol "_isScalingFunction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ScalingFunction)))) ((:*:) (S1 (MetaSel (Just Symbol "_isName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_isId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

iconStyle :: IconStyle Source #

Creates a value of IconStyle with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

isScalingFunction :: Lens' IconStyle (Maybe ScalingFunction) Source #

The function used to scale shapes. Required when a scaledShape is specified.

isName :: Lens' IconStyle (Maybe Text) Source #

Stock icon name. To use a stock icon, prefix it with 'gx_'. See Stock icon names for valid icon names. For example, to specify small_red, set name to 'gx_small_red'.

isId :: Lens' IconStyle (Maybe Text) Source #

Custom icon id.

DisplayRule

data DisplayRule Source #

A display rule of the vector style.

See: displayRule smart constructor.

Instances

Eq DisplayRule Source # 
Data DisplayRule Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DisplayRule -> c DisplayRule #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DisplayRule #

toConstr :: DisplayRule -> Constr #

dataTypeOf :: DisplayRule -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DisplayRule) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DisplayRule) #

gmapT :: (forall b. Data b => b -> b) -> DisplayRule -> DisplayRule #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DisplayRule -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DisplayRule -> r #

gmapQ :: (forall d. Data d => d -> u) -> DisplayRule -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DisplayRule -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DisplayRule -> m DisplayRule #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DisplayRule -> m DisplayRule #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DisplayRule -> m DisplayRule #

Show DisplayRule Source # 
Generic DisplayRule Source # 

Associated Types

type Rep DisplayRule :: * -> * #

ToJSON DisplayRule Source # 
FromJSON DisplayRule Source # 
type Rep DisplayRule Source # 

displayRule :: DisplayRule Source #

Creates a value of DisplayRule with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

drPointOptions :: Lens' DisplayRule (Maybe PointStyle) Source #

Style applied to points. Required for Point Geometry.

drPolygonOptions :: Lens' DisplayRule (Maybe PolygonStyle) Source #

Style applied to polygons. Required for Polygon Geometry.

drZoomLevels :: Lens' DisplayRule (Maybe ZoomLevels) Source #

The zoom levels that this display rule apply.

drFilters :: Lens' DisplayRule [Filter] Source #

This display rule will only be applied to features that match all of the filters here. If filters is empty, then the rule applies to all features.

drName :: Lens' DisplayRule (Maybe Text) Source #

Display rule name. Name is not unique and cannot be used for identification purpose.

drLineOptions :: Lens' DisplayRule (Maybe LineStyle) Source #

Style applied to lines. Required for LineString Geometry.

BOrder

data BOrder Source #

Border in line style. Both color and width are required.

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.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "BOrder'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_boColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_boWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_boOpacity") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))))))

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:

boColor :: Lens' BOrder (Maybe Text) Source #

Color of the border.

boWidth :: Lens' BOrder (Maybe Double) Source #

Width of the border, in pixels.

boOpacity :: Lens' BOrder (Maybe Double) Source #

Opacity of the border.

Map

data Map Source #

A Map is a collection of Layers, optionally contained within folders.

See: map' smart constructor.

Instances

Eq Map Source # 

Methods

(==) :: Map -> Map -> Bool #

(/=) :: Map -> Map -> Bool #

Data Map Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Map -> c Map #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Map #

toConstr :: Map -> Constr #

dataTypeOf :: Map -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Map) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Map) #

gmapT :: (forall b. Data b => b -> b) -> Map -> Map #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Map -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Map -> r #

gmapQ :: (forall d. Data d => d -> u) -> Map -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Map -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Map -> m Map #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Map -> m Map #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Map -> m Map #

Show Map Source # 

Methods

showsPrec :: Int -> Map -> ShowS #

show :: Map -> String #

showList :: [Map] -> ShowS #

Generic Map Source # 

Associated Types

type Rep Map :: * -> * #

Methods

from :: Map -> Rep Map x #

to :: Rep Map x -> Map #

ToJSON Map Source # 
FromJSON Map Source # 
type Rep Map Source # 
type Rep Map = D1 (MetaData "Map" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Map'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_mCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_mWritersCanEditPermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_mEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_mDefaultViewport") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Double]))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_mContents") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [MapItem]))) (S1 (MetaSel (Just Symbol "_mPublishingStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MapPublishingStatus)))) ((:*:) (S1 (MetaSel (Just Symbol "_mCreatorEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_mLastModifiedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_mLastModifierEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_mVersions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_mName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_mBbox") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Double]))) ((:*:) (S1 (MetaSel (Just Symbol "_mProcessingStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe MapProcessingStatus))) (S1 (MetaSel (Just Symbol "_mId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_mProjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_mDraftAccessList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_mPublishedAccessList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_mDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_mTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))))))))

mCreationTime :: Lens' Map (Maybe UTCTime) Source #

The creation time of this map. The value is an RFC 3339 formatted date-time value (e.g. 1970-01-01T00:00:00Z).

mWritersCanEditPermissions :: Lens' Map (Maybe Bool) Source #

If true, WRITERs of the asset are able to edit the asset permissions.

mEtag :: Lens' Map (Maybe Text) Source #

The ETag, used to refer to the current version of the asset.

mDefaultViewport :: Lens' Map [Double] Source #

An array of four numbers (west, south, east, north) which defines the rectangular bounding box of the default viewport. The numbers represent latitude and longitude in decimal degrees.

mContents :: Lens' Map [MapItem] Source #

The contents of this Map.

mPublishingStatus :: Lens' Map (Maybe MapPublishingStatus) Source #

The publishing status of this map.

mCreatorEmail :: Lens' Map (Maybe Text) Source #

The email address of the creator of this map. This is only returned on GET requests and not LIST requests.

mLastModifiedTime :: Lens' Map (Maybe UTCTime) Source #

The last modified time of this map. The value is an RFC 3339 formatted date-time value (e.g. 1970-01-01T00:00:00Z).

mLastModifierEmail :: Lens' Map (Maybe Text) Source #

The email address of the last modifier of this map. This is only returned on GET requests and not LIST requests.

mVersions :: Lens' Map [Text] Source #

Deprecated: An array containing the available versions of this Map. Currently may only contain "published". The publishingStatus field should be used instead.

mName :: Lens' Map (Maybe Text) Source #

The name of this Map, supplied by the author.

mBbox :: Lens' Map [Double] Source #

A rectangular bounding box which contains all of the data in this Map. The box is expressed as \"west, south, east, north\". The numbers represent latitude and longitude in decimal degrees.

mProcessingStatus :: Lens' Map (Maybe MapProcessingStatus) Source #

The processing status of this map. Map processing is automatically started once a map becomes ready for processing.

mId :: Lens' Map (Maybe Text) Source #

A globally unique ID, used to refer to this Map.

mProjectId :: Lens' Map (Maybe Text) Source #

The ID of the project that this Map is in.

mDraftAccessList :: Lens' Map (Maybe Text) Source #

Deprecated: The name of an access list of the Map Editor type. The user on whose behalf the request is being sent must be an editor on that access list. Note: Google Maps Engine no longer uses access lists. Instead, each asset has its own list of permissions. For backward compatibility, the API still accepts access lists for projects that are already using access lists. If you created a GME account/project after July 14th, 2014, you will not be able to send API requests that include access lists. Note: This is an input field only. It is not returned in response to a list or get request.

mPublishedAccessList :: Lens' Map (Maybe Text) Source #

Deprecated: The access list to whom view permissions are granted. The value must be the name of a Maps Engine access list of the Map Viewer type, and the user must be a viewer on that list. Note: Google Maps Engine no longer uses access lists. Instead, each asset has its own list of permissions. For backward compatibility, the API still accepts access lists for projects that are already using access lists. If you created a GME account/project after July 14th, 2014, you will not be able to send API requests that include access lists. This is an input field only. It is not returned in response to a list or get request.

mDescription :: Lens' Map (Maybe Text) Source #

The description of this Map, supplied by the author.

mTags :: Lens' Map [Text] Source #

Tags of this Map.

MapLayerType

data MapLayerType Source #

Identifies this object as a MapLayer.

Constructors

MLTLayer
layer

Instances

Enum MapLayerType Source # 
Eq MapLayerType Source # 
Data MapLayerType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MapLayerType -> c MapLayerType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MapLayerType #

toConstr :: MapLayerType -> Constr #

dataTypeOf :: MapLayerType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MapLayerType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MapLayerType) #

gmapT :: (forall b. Data b => b -> b) -> MapLayerType -> MapLayerType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MapLayerType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MapLayerType -> r #

gmapQ :: (forall d. Data d => d -> u) -> MapLayerType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MapLayerType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MapLayerType -> m MapLayerType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MapLayerType -> m MapLayerType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MapLayerType -> m MapLayerType #

Ord MapLayerType Source # 
Read MapLayerType Source # 
Show MapLayerType Source # 
Generic MapLayerType Source # 

Associated Types

type Rep MapLayerType :: * -> * #

Hashable MapLayerType Source # 
ToJSON MapLayerType Source # 
FromJSON MapLayerType Source # 
FromHttpApiData MapLayerType Source # 
ToHttpApiData MapLayerType Source # 
type Rep MapLayerType Source # 
type Rep MapLayerType = D1 (MetaData "MapLayerType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "MLTLayer" PrefixI False) U1)

RasterCollectionsRastersListResponse

data RasterCollectionsRastersListResponse Source #

The response returned by a call to rasterCollections.rasters.List.

See: rasterCollectionsRastersListResponse smart constructor.

Instances

Eq RasterCollectionsRastersListResponse Source # 
Data RasterCollectionsRastersListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RasterCollectionsRastersListResponse -> c RasterCollectionsRastersListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RasterCollectionsRastersListResponse #

toConstr :: RasterCollectionsRastersListResponse -> Constr #

dataTypeOf :: RasterCollectionsRastersListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RasterCollectionsRastersListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RasterCollectionsRastersListResponse) #

gmapT :: (forall b. Data b => b -> b) -> RasterCollectionsRastersListResponse -> RasterCollectionsRastersListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RasterCollectionsRastersListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RasterCollectionsRastersListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> RasterCollectionsRastersListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RasterCollectionsRastersListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RasterCollectionsRastersListResponse -> m RasterCollectionsRastersListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionsRastersListResponse -> m RasterCollectionsRastersListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionsRastersListResponse -> m RasterCollectionsRastersListResponse #

Show RasterCollectionsRastersListResponse Source # 
Generic RasterCollectionsRastersListResponse Source # 
ToJSON RasterCollectionsRastersListResponse Source # 
FromJSON RasterCollectionsRastersListResponse Source # 
type Rep RasterCollectionsRastersListResponse Source # 
type Rep RasterCollectionsRastersListResponse = D1 (MetaData "RasterCollectionsRastersListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "RasterCollectionsRastersListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rcrlrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rcrlrRasters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [RasterCollectionsRaster])))))

rasterCollectionsRastersListResponse :: RasterCollectionsRastersListResponse Source #

Creates a value of RasterCollectionsRastersListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

GeoJSONMultiLineString

data GeoJSONMultiLineString Source #

Multi Line String

See: geoJSONMultiLineString smart constructor.

Instances

Eq GeoJSONMultiLineString Source # 
Data GeoJSONMultiLineString Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeoJSONMultiLineString -> c GeoJSONMultiLineString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeoJSONMultiLineString #

toConstr :: GeoJSONMultiLineString -> Constr #

dataTypeOf :: GeoJSONMultiLineString -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GeoJSONMultiLineString) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeoJSONMultiLineString) #

gmapT :: (forall b. Data b => b -> b) -> GeoJSONMultiLineString -> GeoJSONMultiLineString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONMultiLineString -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONMultiLineString -> r #

gmapQ :: (forall d. Data d => d -> u) -> GeoJSONMultiLineString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GeoJSONMultiLineString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GeoJSONMultiLineString -> m GeoJSONMultiLineString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONMultiLineString -> m GeoJSONMultiLineString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONMultiLineString -> m GeoJSONMultiLineString #

Show GeoJSONMultiLineString Source # 
Generic GeoJSONMultiLineString Source # 
ToJSON GeoJSONMultiLineString Source # 
FromJSON GeoJSONMultiLineString Source # 
type Rep GeoJSONMultiLineString Source # 
type Rep GeoJSONMultiLineString = D1 (MetaData "GeoJSONMultiLineString" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "GeoJSONMultiLineString'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gjmlsCoordinates") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [[[Textual Double]]]))) (S1 (MetaSel (Just Symbol "_gjmlsType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GeoJSONMultiLineStringType)))))

geoJSONMultiLineString :: GeoJSONMultiLineString Source #

Creates a value of GeoJSONMultiLineString with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gjmlsCoordinates :: Lens' GeoJSONMultiLineString [[[Double]]] Source #

An array of at least two GeoJsonLineString coordinate arrays.

gjmlsType :: Lens' GeoJSONMultiLineString (Maybe GeoJSONMultiLineStringType) Source #

Identifies this object as a GeoJsonMultiLineString.

ScalingFunction

data ScalingFunction Source #

Parameters for scaling scaled shapes.

See: scalingFunction smart constructor.

Instances

Eq ScalingFunction Source # 
Data ScalingFunction Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ScalingFunction -> c ScalingFunction #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ScalingFunction #

toConstr :: ScalingFunction -> Constr #

dataTypeOf :: ScalingFunction -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ScalingFunction) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ScalingFunction) #

gmapT :: (forall b. Data b => b -> b) -> ScalingFunction -> ScalingFunction #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ScalingFunction -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ScalingFunction -> r #

gmapQ :: (forall d. Data d => d -> u) -> ScalingFunction -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ScalingFunction -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ScalingFunction -> m ScalingFunction #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalingFunction -> m ScalingFunction #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ScalingFunction -> m ScalingFunction #

Show ScalingFunction Source # 
Generic ScalingFunction Source # 
ToJSON ScalingFunction Source # 
FromJSON ScalingFunction Source # 
type Rep ScalingFunction Source # 
type Rep ScalingFunction = D1 (MetaData "ScalingFunction" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "ScalingFunction'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_sfValueRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ValueRange))) (S1 (MetaSel (Just Symbol "_sfSizeRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe SizeRange)))) ((:*:) (S1 (MetaSel (Just Symbol "_sfScalingType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ScalingFunctionScalingType))) (S1 (MetaSel (Just Symbol "_sfColumn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

scalingFunction :: ScalingFunction Source #

Creates a value of ScalingFunction with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

sfValueRange :: Lens' ScalingFunction (Maybe ValueRange) Source #

The range of values to display across the size range.

sfSizeRange :: Lens' ScalingFunction (Maybe SizeRange) Source #

The range of shape sizes, in pixels. For circles, the size corresponds to the diameter.

sfScalingType :: Lens' ScalingFunction (Maybe ScalingFunctionScalingType) Source #

The type of scaling function to use. Defaults to SQRT. Currently only linear and square root scaling are supported.

sfColumn :: Lens' ScalingFunction (Maybe Text) Source #

Name of the numeric column used to scale a shape.

LabelStyleFontWeight

data LabelStyleFontWeight Source #

Font weight of the label, defaults to 'normal'.

Constructors

Bold
bold
Normal
normal

Instances

Enum LabelStyleFontWeight Source # 
Eq LabelStyleFontWeight Source # 
Data LabelStyleFontWeight Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LabelStyleFontWeight -> c LabelStyleFontWeight #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LabelStyleFontWeight #

toConstr :: LabelStyleFontWeight -> Constr #

dataTypeOf :: LabelStyleFontWeight -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LabelStyleFontWeight) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LabelStyleFontWeight) #

gmapT :: (forall b. Data b => b -> b) -> LabelStyleFontWeight -> LabelStyleFontWeight #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LabelStyleFontWeight -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LabelStyleFontWeight -> r #

gmapQ :: (forall d. Data d => d -> u) -> LabelStyleFontWeight -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LabelStyleFontWeight -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LabelStyleFontWeight -> m LabelStyleFontWeight #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LabelStyleFontWeight -> m LabelStyleFontWeight #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LabelStyleFontWeight -> m LabelStyleFontWeight #

Ord LabelStyleFontWeight Source # 
Read LabelStyleFontWeight Source # 
Show LabelStyleFontWeight Source # 
Generic LabelStyleFontWeight Source # 
Hashable LabelStyleFontWeight Source # 
ToJSON LabelStyleFontWeight Source # 
FromJSON LabelStyleFontWeight Source # 
FromHttpApiData LabelStyleFontWeight Source # 
ToHttpApiData LabelStyleFontWeight Source # 
type Rep LabelStyleFontWeight Source # 
type Rep LabelStyleFontWeight = D1 (MetaData "LabelStyleFontWeight" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "Bold" PrefixI False) U1) (C1 (MetaCons "Normal" PrefixI False) U1))

MapFolderType

data MapFolderType Source #

Identifies this object as a MapFolder.

Constructors

Folder
folder

Instances

Enum MapFolderType Source # 
Eq MapFolderType Source # 
Data MapFolderType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MapFolderType -> c MapFolderType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MapFolderType #

toConstr :: MapFolderType -> Constr #

dataTypeOf :: MapFolderType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MapFolderType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MapFolderType) #

gmapT :: (forall b. Data b => b -> b) -> MapFolderType -> MapFolderType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MapFolderType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MapFolderType -> r #

gmapQ :: (forall d. Data d => d -> u) -> MapFolderType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MapFolderType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MapFolderType -> m MapFolderType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MapFolderType -> m MapFolderType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MapFolderType -> m MapFolderType #

Ord MapFolderType Source # 
Read MapFolderType Source # 
Show MapFolderType Source # 
Generic MapFolderType Source # 

Associated Types

type Rep MapFolderType :: * -> * #

Hashable MapFolderType Source # 
ToJSON MapFolderType Source # 
FromJSON MapFolderType Source # 
FromHttpApiData MapFolderType Source # 
ToHttpApiData MapFolderType Source # 
type Rep MapFolderType Source # 
type Rep MapFolderType = D1 (MetaData "MapFolderType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Folder" PrefixI False) U1)

RasterCollectionProcessingStatus

data RasterCollectionProcessingStatus Source #

The processing status of this RasterCollection.

Constructors

RCPSComplete
complete
RCPSFailed
failed
RCPSNotReady
notReady
RCPSProcessing
processing
RCPSReady
ready

Instances

Enum RasterCollectionProcessingStatus Source # 
Eq RasterCollectionProcessingStatus Source # 
Data RasterCollectionProcessingStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RasterCollectionProcessingStatus -> c RasterCollectionProcessingStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RasterCollectionProcessingStatus #

toConstr :: RasterCollectionProcessingStatus -> Constr #

dataTypeOf :: RasterCollectionProcessingStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RasterCollectionProcessingStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RasterCollectionProcessingStatus) #

gmapT :: (forall b. Data b => b -> b) -> RasterCollectionProcessingStatus -> RasterCollectionProcessingStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RasterCollectionProcessingStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RasterCollectionProcessingStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> RasterCollectionProcessingStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RasterCollectionProcessingStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RasterCollectionProcessingStatus -> m RasterCollectionProcessingStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionProcessingStatus -> m RasterCollectionProcessingStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionProcessingStatus -> m RasterCollectionProcessingStatus #

Ord RasterCollectionProcessingStatus Source # 
Read RasterCollectionProcessingStatus Source # 
Show RasterCollectionProcessingStatus Source # 
Generic RasterCollectionProcessingStatus Source # 
Hashable RasterCollectionProcessingStatus Source # 
ToJSON RasterCollectionProcessingStatus Source # 
FromJSON RasterCollectionProcessingStatus Source # 
FromHttpApiData RasterCollectionProcessingStatus Source # 
ToHttpApiData RasterCollectionProcessingStatus Source # 
type Rep RasterCollectionProcessingStatus Source # 
type Rep RasterCollectionProcessingStatus = D1 (MetaData "RasterCollectionProcessingStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "RCPSComplete" PrefixI False) U1) (C1 (MetaCons "RCPSFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RCPSNotReady" PrefixI False) U1) ((:+:) (C1 (MetaCons "RCPSProcessing" PrefixI False) U1) (C1 (MetaCons "RCPSReady" PrefixI False) U1))))

TablesFeaturesListVersion

data TablesFeaturesListVersion Source #

The table version to access. See Accessing Public Data for information.

Constructors

TFLVDraft

draft The draft version.

TFLVPublished

published The published version.

Instances

Enum TablesFeaturesListVersion Source # 
Eq TablesFeaturesListVersion Source # 
Data TablesFeaturesListVersion Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TablesFeaturesListVersion -> c TablesFeaturesListVersion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TablesFeaturesListVersion #

toConstr :: TablesFeaturesListVersion -> Constr #

dataTypeOf :: TablesFeaturesListVersion -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TablesFeaturesListVersion) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TablesFeaturesListVersion) #

gmapT :: (forall b. Data b => b -> b) -> TablesFeaturesListVersion -> TablesFeaturesListVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TablesFeaturesListVersion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TablesFeaturesListVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> TablesFeaturesListVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TablesFeaturesListVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TablesFeaturesListVersion -> m TablesFeaturesListVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TablesFeaturesListVersion -> m TablesFeaturesListVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TablesFeaturesListVersion -> m TablesFeaturesListVersion #

Ord TablesFeaturesListVersion Source # 
Read TablesFeaturesListVersion Source # 
Show TablesFeaturesListVersion Source # 
Generic TablesFeaturesListVersion Source # 
Hashable TablesFeaturesListVersion Source # 
ToJSON TablesFeaturesListVersion Source # 
FromJSON TablesFeaturesListVersion Source # 
FromHttpApiData TablesFeaturesListVersion Source # 
ToHttpApiData TablesFeaturesListVersion Source # 
type Rep TablesFeaturesListVersion Source # 
type Rep TablesFeaturesListVersion = D1 (MetaData "TablesFeaturesListVersion" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "TFLVDraft" PrefixI False) U1) (C1 (MetaCons "TFLVPublished" PrefixI False) U1))

MapsListProcessingStatus

data MapsListProcessingStatus Source #

Constructors

MLPSComplete

complete The map has completed processing.

MLPSFailed

failed The map has failed processing.

MLPSNotReady

notReady The map is not ready for processing.

MLPSProcessing

processing The map is processing.

Instances

Enum MapsListProcessingStatus Source # 
Eq MapsListProcessingStatus Source # 
Data MapsListProcessingStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MapsListProcessingStatus -> c MapsListProcessingStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MapsListProcessingStatus #

toConstr :: MapsListProcessingStatus -> Constr #

dataTypeOf :: MapsListProcessingStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MapsListProcessingStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MapsListProcessingStatus) #

gmapT :: (forall b. Data b => b -> b) -> MapsListProcessingStatus -> MapsListProcessingStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MapsListProcessingStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MapsListProcessingStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> MapsListProcessingStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MapsListProcessingStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MapsListProcessingStatus -> m MapsListProcessingStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MapsListProcessingStatus -> m MapsListProcessingStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MapsListProcessingStatus -> m MapsListProcessingStatus #

Ord MapsListProcessingStatus Source # 
Read MapsListProcessingStatus Source # 
Show MapsListProcessingStatus Source # 
Generic MapsListProcessingStatus Source # 
Hashable MapsListProcessingStatus Source # 
ToJSON MapsListProcessingStatus Source # 
FromJSON MapsListProcessingStatus Source # 
FromHttpApiData MapsListProcessingStatus Source # 
ToHttpApiData MapsListProcessingStatus Source # 
type Rep MapsListProcessingStatus Source # 
type Rep MapsListProcessingStatus = D1 (MetaData "MapsListProcessingStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "MLPSComplete" PrefixI False) U1) (C1 (MetaCons "MLPSFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "MLPSNotReady" PrefixI False) U1) (C1 (MetaCons "MLPSProcessing" PrefixI False) U1)))

AssetsListResponse

data AssetsListResponse Source #

The response returned by a call to resources.List.

See: assetsListResponse smart constructor.

Instances

Eq AssetsListResponse Source # 
Data AssetsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AssetsListResponse -> c AssetsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AssetsListResponse #

toConstr :: AssetsListResponse -> Constr #

dataTypeOf :: AssetsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AssetsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AssetsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> AssetsListResponse -> AssetsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AssetsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AssetsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> AssetsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AssetsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AssetsListResponse -> m AssetsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AssetsListResponse -> m AssetsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AssetsListResponse -> m AssetsListResponse #

Show AssetsListResponse Source # 
Generic AssetsListResponse Source # 
ToJSON AssetsListResponse Source # 
FromJSON AssetsListResponse Source # 
type Rep AssetsListResponse Source # 
type Rep AssetsListResponse = D1 (MetaData "AssetsListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "AssetsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_alrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bytes))) (S1 (MetaSel (Just Symbol "_alrAssets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Asset])))))

assetsListResponse :: AssetsListResponse Source #

Creates a value of AssetsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

PublishResponse

data PublishResponse Source #

The response returned by a call to any asset's Publish method.

See: publishResponse smart constructor.

Instances

Eq PublishResponse Source # 
Data PublishResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PublishResponse -> c PublishResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PublishResponse #

toConstr :: PublishResponse -> Constr #

dataTypeOf :: PublishResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PublishResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublishResponse) #

gmapT :: (forall b. Data b => b -> b) -> PublishResponse -> PublishResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PublishResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PublishResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> PublishResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PublishResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PublishResponse -> m PublishResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PublishResponse -> m PublishResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PublishResponse -> m PublishResponse #

Show PublishResponse Source # 
Generic PublishResponse Source # 
ToJSON PublishResponse Source # 
FromJSON PublishResponse Source # 
type Rep PublishResponse Source # 
type Rep PublishResponse = D1 (MetaData "PublishResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "PublishResponse'" PrefixI False) U1)

publishResponse :: PublishResponse Source #

Creates a value of PublishResponse with the minimum fields required to make a request.

FeaturesBatchInsertRequest

data FeaturesBatchInsertRequest Source #

The request sent to features.Insert.

See: featuresBatchInsertRequest smart constructor.

Instances

Eq FeaturesBatchInsertRequest Source # 
Data FeaturesBatchInsertRequest Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FeaturesBatchInsertRequest -> c FeaturesBatchInsertRequest #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FeaturesBatchInsertRequest #

toConstr :: FeaturesBatchInsertRequest -> Constr #

dataTypeOf :: FeaturesBatchInsertRequest -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FeaturesBatchInsertRequest) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FeaturesBatchInsertRequest) #

gmapT :: (forall b. Data b => b -> b) -> FeaturesBatchInsertRequest -> FeaturesBatchInsertRequest #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FeaturesBatchInsertRequest -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FeaturesBatchInsertRequest -> r #

gmapQ :: (forall d. Data d => d -> u) -> FeaturesBatchInsertRequest -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FeaturesBatchInsertRequest -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FeaturesBatchInsertRequest -> m FeaturesBatchInsertRequest #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FeaturesBatchInsertRequest -> m FeaturesBatchInsertRequest #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FeaturesBatchInsertRequest -> m FeaturesBatchInsertRequest #

Show FeaturesBatchInsertRequest Source # 
Generic FeaturesBatchInsertRequest Source # 
ToJSON FeaturesBatchInsertRequest Source # 
FromJSON FeaturesBatchInsertRequest Source # 
type Rep FeaturesBatchInsertRequest Source # 
type Rep FeaturesBatchInsertRequest = D1 (MetaData "FeaturesBatchInsertRequest" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "FeaturesBatchInsertRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fbirFeatures") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Feature]))) (S1 (MetaSel (Just Symbol "_fbirNormalizeGeometries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Bool))))

featuresBatchInsertRequest :: FeaturesBatchInsertRequest Source #

Creates a value of FeaturesBatchInsertRequest with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

fbirNormalizeGeometries :: Lens' FeaturesBatchInsertRequest Bool Source #

If true, the server will normalize feature geometries. It is assumed that the South Pole is exterior to any polygons given. See here for a list of normalizations. If false, all feature geometries must be given already normalized. The points in all LinearRings must be listed in counter-clockwise order, and LinearRings may not intersect.

Datasource

data Datasource Source #

Instances

Eq Datasource Source # 
Data Datasource Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Datasource -> c Datasource #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Datasource #

toConstr :: Datasource -> Constr #

dataTypeOf :: Datasource -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Datasource) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Datasource) #

gmapT :: (forall b. Data b => b -> b) -> Datasource -> Datasource #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Datasource -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Datasource -> r #

gmapQ :: (forall d. Data d => d -> u) -> Datasource -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Datasource -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Datasource -> m Datasource #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Datasource -> m Datasource #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Datasource -> m Datasource #

Show Datasource Source # 
Generic Datasource Source # 

Associated Types

type Rep Datasource :: * -> * #

ToJSON Datasource Source # 
FromJSON Datasource Source # 
type Rep Datasource Source # 
type Rep Datasource = D1 (MetaData "Datasource" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" True) (C1 (MetaCons "Datasource'" PrefixI True) (S1 (MetaSel (Just Symbol "_dId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

datasource :: Datasource Source #

Creates a value of Datasource with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

dId :: Lens' Datasource (Maybe Text) Source #

The ID of a datasource.

LabelStyleFontStyle

data LabelStyleFontStyle Source #

Font style of the label, defaults to 'normal'.

Constructors

LSFSItalic
italic
LSFSNormal
normal

Instances

Enum LabelStyleFontStyle Source # 
Eq LabelStyleFontStyle Source # 
Data LabelStyleFontStyle Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LabelStyleFontStyle -> c LabelStyleFontStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LabelStyleFontStyle #

toConstr :: LabelStyleFontStyle -> Constr #

dataTypeOf :: LabelStyleFontStyle -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LabelStyleFontStyle) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LabelStyleFontStyle) #

gmapT :: (forall b. Data b => b -> b) -> LabelStyleFontStyle -> LabelStyleFontStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LabelStyleFontStyle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LabelStyleFontStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> LabelStyleFontStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LabelStyleFontStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LabelStyleFontStyle -> m LabelStyleFontStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LabelStyleFontStyle -> m LabelStyleFontStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LabelStyleFontStyle -> m LabelStyleFontStyle #

Ord LabelStyleFontStyle Source # 
Read LabelStyleFontStyle Source # 
Show LabelStyleFontStyle Source # 
Generic LabelStyleFontStyle Source # 
Hashable LabelStyleFontStyle Source # 
ToJSON LabelStyleFontStyle Source # 
FromJSON LabelStyleFontStyle Source # 
FromHttpApiData LabelStyleFontStyle Source # 
ToHttpApiData LabelStyleFontStyle Source # 
type Rep LabelStyleFontStyle Source # 
type Rep LabelStyleFontStyle = D1 (MetaData "LabelStyleFontStyle" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "LSFSItalic" PrefixI False) U1) (C1 (MetaCons "LSFSNormal" PrefixI False) U1))

RasterCollectionsRaster

data RasterCollectionsRaster Source #

A raster resource.

See: rasterCollectionsRaster smart constructor.

Instances

Eq RasterCollectionsRaster Source # 
Data RasterCollectionsRaster Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RasterCollectionsRaster -> c RasterCollectionsRaster #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RasterCollectionsRaster #

toConstr :: RasterCollectionsRaster -> Constr #

dataTypeOf :: RasterCollectionsRaster -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RasterCollectionsRaster) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RasterCollectionsRaster) #

gmapT :: (forall b. Data b => b -> b) -> RasterCollectionsRaster -> RasterCollectionsRaster #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RasterCollectionsRaster -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RasterCollectionsRaster -> r #

gmapQ :: (forall d. Data d => d -> u) -> RasterCollectionsRaster -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RasterCollectionsRaster -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RasterCollectionsRaster -> m RasterCollectionsRaster #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionsRaster -> m RasterCollectionsRaster #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionsRaster -> m RasterCollectionsRaster #

Show RasterCollectionsRaster Source # 
Generic RasterCollectionsRaster Source # 
ToJSON RasterCollectionsRaster Source # 
FromJSON RasterCollectionsRaster Source # 
type Rep RasterCollectionsRaster Source # 

rasterCollectionsRaster :: RasterCollectionsRaster Source #

Creates a value of RasterCollectionsRaster with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

rcrCreationTime :: Lens' RasterCollectionsRaster (Maybe UTCTime) Source #

The creation time of this raster. The value is an RFC 3339 formatted date-time value (e.g. 1970-01-01T00:00:00Z).

rcrRasterType :: Lens' RasterCollectionsRaster Text Source #

The type of this Raster. Always "image" today.

rcrLastModifiedTime :: Lens' RasterCollectionsRaster (Maybe UTCTime) Source #

The last modified time of this raster. The value is an RFC 3339 formatted date-time value (e.g. 1970-01-01T00:00:00Z).

rcrName :: Lens' RasterCollectionsRaster (Maybe Text) Source #

The name of this Raster, supplied by the author.

rcrBbox :: Lens' RasterCollectionsRaster [Double] Source #

A rectangular bounding box which contains all of the data in this Raster. The box is expressed as \"west, south, east, north\". The numbers represent latitudes and longitudes in decimal degrees.

rcrId :: Lens' RasterCollectionsRaster (Maybe Text) Source #

A globally unique ID, used to refer to this Raster.

rcrProjectId :: Lens' RasterCollectionsRaster (Maybe Text) Source #

The ID of the project that this Raster is in.

rcrDescription :: Lens' RasterCollectionsRaster (Maybe Text) Source #

The description of this Raster, supplied by the author.

Filter

data Filter Source #

Conditions for filtering features.

See: filter' smart constructor.

Instances

Eq Filter Source # 

Methods

(==) :: Filter -> Filter -> Bool #

(/=) :: Filter -> Filter -> Bool #

Data Filter Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Filter -> c Filter #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Filter #

toConstr :: Filter -> Constr #

dataTypeOf :: Filter -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Filter) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Filter) #

gmapT :: (forall b. Data b => b -> b) -> Filter -> Filter #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Filter -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Filter -> r #

gmapQ :: (forall d. Data d => d -> u) -> Filter -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Filter -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Filter -> m Filter #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Filter -> m Filter #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Filter -> m Filter #

Show Filter Source # 
Generic Filter Source # 

Associated Types

type Rep Filter :: * -> * #

Methods

from :: Filter -> Rep Filter x #

to :: Rep Filter x -> Filter #

ToJSON Filter Source # 
FromJSON Filter Source # 
type Rep Filter Source # 
type Rep Filter = D1 (MetaData "Filter" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Filter'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fOperator") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FilterOperator))) ((:*:) (S1 (MetaSel (Just Symbol "_fValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe JSONValue))) (S1 (MetaSel (Just Symbol "_fColumn") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

filter' :: Filter Source #

Creates a value of Filter with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

fOperator :: Lens' Filter (Maybe FilterOperator) Source #

Operation used to evaluate the filter.

fValue :: Lens' Filter (Maybe JSONValue) Source #

Value to be evaluated against attribute.

fColumn :: Lens' Filter (Maybe Text) Source #

The column name to filter on.

GeoJSONMultiPoint

data GeoJSONMultiPoint Source #

Instances

Eq GeoJSONMultiPoint Source # 
Data GeoJSONMultiPoint Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeoJSONMultiPoint -> c GeoJSONMultiPoint #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeoJSONMultiPoint #

toConstr :: GeoJSONMultiPoint -> Constr #

dataTypeOf :: GeoJSONMultiPoint -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GeoJSONMultiPoint) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeoJSONMultiPoint) #

gmapT :: (forall b. Data b => b -> b) -> GeoJSONMultiPoint -> GeoJSONMultiPoint #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONMultiPoint -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONMultiPoint -> r #

gmapQ :: (forall d. Data d => d -> u) -> GeoJSONMultiPoint -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GeoJSONMultiPoint -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GeoJSONMultiPoint -> m GeoJSONMultiPoint #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONMultiPoint -> m GeoJSONMultiPoint #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONMultiPoint -> m GeoJSONMultiPoint #

Show GeoJSONMultiPoint Source # 
Generic GeoJSONMultiPoint Source # 
ToJSON GeoJSONMultiPoint Source # 
FromJSON GeoJSONMultiPoint Source # 
type Rep GeoJSONMultiPoint Source # 
type Rep GeoJSONMultiPoint = D1 (MetaData "GeoJSONMultiPoint" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "GeoJSONMultiPoint'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gjmpCoordinates") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [[Textual Double]]))) (S1 (MetaSel (Just Symbol "_gjmpType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GeoJSONMultiPointType)))))

geoJSONMultiPoint :: GeoJSONMultiPoint Source #

Creates a value of GeoJSONMultiPoint with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gjmpCoordinates :: Lens' GeoJSONMultiPoint [[Double]] Source #

An array of at least two GeoJsonPoint coordinate arrays.

gjmpType :: Lens' GeoJSONMultiPoint (Maybe GeoJSONMultiPointType) Source #

Identifies this object as a GeoJsonMultiPoint.

AssetType

data AssetType Source #

The type of asset. One of raster, rasterCollection, table, map, or layer.

Constructors

ATLayer
layer
ATMap
map
ATRaster
raster
ATRasterCollection
rasterCollection
ATTable
table

Instances

Enum AssetType Source # 
Eq AssetType Source # 
Data AssetType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AssetType -> c AssetType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AssetType #

toConstr :: AssetType -> Constr #

dataTypeOf :: AssetType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AssetType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AssetType) #

gmapT :: (forall b. Data b => b -> b) -> AssetType -> AssetType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AssetType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AssetType -> r #

gmapQ :: (forall d. Data d => d -> u) -> AssetType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AssetType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AssetType -> m AssetType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AssetType -> m AssetType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AssetType -> m AssetType #

Ord AssetType Source # 
Read AssetType Source # 
Show AssetType Source # 
Generic AssetType Source # 

Associated Types

type Rep AssetType :: * -> * #

Hashable AssetType Source # 
ToJSON AssetType Source # 
FromJSON AssetType Source # 
FromHttpApiData AssetType Source # 
ToHttpApiData AssetType Source # 
type Rep AssetType Source # 
type Rep AssetType = D1 (MetaData "AssetType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "ATLayer" PrefixI False) U1) (C1 (MetaCons "ATMap" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ATRaster" PrefixI False) U1) ((:+:) (C1 (MetaCons "ATRasterCollection" PrefixI False) U1) (C1 (MetaCons "ATTable" PrefixI False) U1))))

RasterRasterType

data RasterRasterType Source #

The type of this Raster. Always "image" today.

Constructors

RRTImage
image

Instances

Enum RasterRasterType Source # 
Eq RasterRasterType Source # 
Data RasterRasterType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RasterRasterType -> c RasterRasterType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RasterRasterType #

toConstr :: RasterRasterType -> Constr #

dataTypeOf :: RasterRasterType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RasterRasterType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RasterRasterType) #

gmapT :: (forall b. Data b => b -> b) -> RasterRasterType -> RasterRasterType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RasterRasterType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RasterRasterType -> r #

gmapQ :: (forall d. Data d => d -> u) -> RasterRasterType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RasterRasterType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RasterRasterType -> m RasterRasterType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterRasterType -> m RasterRasterType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterRasterType -> m RasterRasterType #

Ord RasterRasterType Source # 
Read RasterRasterType Source # 
Show RasterRasterType Source # 
Generic RasterRasterType Source # 
Hashable RasterRasterType Source # 
ToJSON RasterRasterType Source # 
FromJSON RasterRasterType Source # 
FromHttpApiData RasterRasterType Source # 
ToHttpApiData RasterRasterType Source # 
type Rep RasterRasterType Source # 
type Rep RasterRasterType = D1 (MetaData "RasterRasterType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "RRTImage" PrefixI False) U1)

RasterCollectionsListRole

data RasterCollectionsListRole Source #

The role parameter indicates that the response should only contain assets where the current user has the specified level of access.

Constructors

RCLROwner

owner The user can read, write and administer the asset.

RCLRReader

reader The user can read the asset.

RCLRWriter

writer The user can read and write the asset.

Instances

Enum RasterCollectionsListRole Source # 
Eq RasterCollectionsListRole Source # 
Data RasterCollectionsListRole Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RasterCollectionsListRole -> c RasterCollectionsListRole #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RasterCollectionsListRole #

toConstr :: RasterCollectionsListRole -> Constr #

dataTypeOf :: RasterCollectionsListRole -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RasterCollectionsListRole) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RasterCollectionsListRole) #

gmapT :: (forall b. Data b => b -> b) -> RasterCollectionsListRole -> RasterCollectionsListRole #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RasterCollectionsListRole -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RasterCollectionsListRole -> r #

gmapQ :: (forall d. Data d => d -> u) -> RasterCollectionsListRole -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RasterCollectionsListRole -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RasterCollectionsListRole -> m RasterCollectionsListRole #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionsListRole -> m RasterCollectionsListRole #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionsListRole -> m RasterCollectionsListRole #

Ord RasterCollectionsListRole Source # 
Read RasterCollectionsListRole Source # 
Show RasterCollectionsListRole Source # 
Generic RasterCollectionsListRole Source # 
Hashable RasterCollectionsListRole Source # 
ToJSON RasterCollectionsListRole Source # 
FromJSON RasterCollectionsListRole Source # 
FromHttpApiData RasterCollectionsListRole Source # 
ToHttpApiData RasterCollectionsListRole Source # 
type Rep RasterCollectionsListRole Source # 
type Rep RasterCollectionsListRole = D1 (MetaData "RasterCollectionsListRole" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "RCLROwner" PrefixI False) U1) ((:+:) (C1 (MetaCons "RCLRReader" PrefixI False) U1) (C1 (MetaCons "RCLRWriter" PrefixI False) U1)))

FilterOperator

data FilterOperator Source #

Operation used to evaluate the filter.

Instances

Enum FilterOperator Source # 
Eq FilterOperator Source # 
Data FilterOperator Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FilterOperator -> c FilterOperator #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FilterOperator #

toConstr :: FilterOperator -> Constr #

dataTypeOf :: FilterOperator -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FilterOperator) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FilterOperator) #

gmapT :: (forall b. Data b => b -> b) -> FilterOperator -> FilterOperator #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FilterOperator -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FilterOperator -> r #

gmapQ :: (forall d. Data d => d -> u) -> FilterOperator -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FilterOperator -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FilterOperator -> m FilterOperator #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FilterOperator -> m FilterOperator #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FilterOperator -> m FilterOperator #

Ord FilterOperator Source # 
Read FilterOperator Source # 
Show FilterOperator Source # 
Generic FilterOperator Source # 

Associated Types

type Rep FilterOperator :: * -> * #

Hashable FilterOperator Source # 
ToJSON FilterOperator Source # 
FromJSON FilterOperator Source # 
FromHttpApiData FilterOperator Source # 
ToHttpApiData FilterOperator Source # 
type Rep FilterOperator Source # 
type Rep FilterOperator = D1 (MetaData "FilterOperator" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "NotEqual" PrefixI False) U1) (C1 (MetaCons "Less" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LessOrEqual" PrefixI False) U1) (C1 (MetaCons "Equal" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "Greater" PrefixI False) U1) (C1 (MetaCons "GreaterEqual" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Contains" PrefixI False) U1) ((:+:) (C1 (MetaCons "EndsWith" PrefixI False) U1) (C1 (MetaCons "StartsWith" PrefixI False) U1)))))

TableColumnType

data TableColumnType Source #

The type of data stored in this column.

Constructors

Datetime
datetime
Double
double
Integer
integer
LineStrings
lineStrings
MixedGeometry
mixedGeometry
Points
points
Polygons
polygons
String
string

Instances

Enum TableColumnType Source # 
Eq TableColumnType Source # 
Data TableColumnType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableColumnType -> c TableColumnType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableColumnType #

toConstr :: TableColumnType -> Constr #

dataTypeOf :: TableColumnType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TableColumnType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableColumnType) #

gmapT :: (forall b. Data b => b -> b) -> TableColumnType -> TableColumnType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableColumnType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableColumnType -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableColumnType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableColumnType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableColumnType -> m TableColumnType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableColumnType -> m TableColumnType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableColumnType -> m TableColumnType #

Ord TableColumnType Source # 
Read TableColumnType Source # 
Show TableColumnType Source # 
Generic TableColumnType Source # 
Hashable TableColumnType Source # 
ToJSON TableColumnType Source # 
FromJSON TableColumnType Source # 
FromHttpApiData TableColumnType Source # 
ToHttpApiData TableColumnType Source # 
type Rep TableColumnType Source # 
type Rep TableColumnType = D1 (MetaData "TableColumnType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Datetime" PrefixI False) U1) (C1 (MetaCons "Double" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Integer" PrefixI False) U1) (C1 (MetaCons "LineStrings" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "MixedGeometry" PrefixI False) U1) (C1 (MetaCons "Points" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Polygons" PrefixI False) U1) (C1 (MetaCons "String" PrefixI False) U1))))

GeoJSONMultiPolygon

data GeoJSONMultiPolygon Source #

Instances

Eq GeoJSONMultiPolygon Source # 
Data GeoJSONMultiPolygon Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeoJSONMultiPolygon -> c GeoJSONMultiPolygon #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeoJSONMultiPolygon #

toConstr :: GeoJSONMultiPolygon -> Constr #

dataTypeOf :: GeoJSONMultiPolygon -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GeoJSONMultiPolygon) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeoJSONMultiPolygon) #

gmapT :: (forall b. Data b => b -> b) -> GeoJSONMultiPolygon -> GeoJSONMultiPolygon #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONMultiPolygon -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONMultiPolygon -> r #

gmapQ :: (forall d. Data d => d -> u) -> GeoJSONMultiPolygon -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GeoJSONMultiPolygon -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GeoJSONMultiPolygon -> m GeoJSONMultiPolygon #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONMultiPolygon -> m GeoJSONMultiPolygon #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONMultiPolygon -> m GeoJSONMultiPolygon #

Show GeoJSONMultiPolygon Source # 
Generic GeoJSONMultiPolygon Source # 
ToJSON GeoJSONMultiPolygon Source # 
FromJSON GeoJSONMultiPolygon Source # 
type Rep GeoJSONMultiPolygon Source # 
type Rep GeoJSONMultiPolygon = D1 (MetaData "GeoJSONMultiPolygon" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "GeoJSONMultiPolygon'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gjsonmpCoordinates") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [[[[Textual Double]]]]))) (S1 (MetaSel (Just Symbol "_gjsonmpType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GeoJSONMultiPolygonType)))))

geoJSONMultiPolygon :: GeoJSONMultiPolygon Source #

Creates a value of GeoJSONMultiPolygon with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gjsonmpCoordinates :: Lens' GeoJSONMultiPolygon [[[[Double]]]] Source #

An array of at least two GeoJsonPolygon coordinate arrays.

gjsonmpType :: Lens' GeoJSONMultiPolygon (Maybe GeoJSONMultiPolygonType) Source #

Identifies this object as a GeoJsonMultiPolygon.

Layer

data Layer Source #

A Layer combines multiple datasources, with styling information, for presentation on a map.

See: layer smart constructor.

Instances

Eq Layer Source # 

Methods

(==) :: Layer -> Layer -> Bool #

(/=) :: Layer -> Layer -> Bool #

Data Layer Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Layer -> c Layer #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Layer #

toConstr :: Layer -> Constr #

dataTypeOf :: Layer -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Layer) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Layer) #

gmapT :: (forall b. Data b => b -> b) -> Layer -> Layer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Layer -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Layer -> r #

gmapQ :: (forall d. Data d => d -> u) -> Layer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Layer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Layer -> m Layer #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Layer -> m Layer #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Layer -> m Layer #

Show Layer Source # 

Methods

showsPrec :: Int -> Layer -> ShowS #

show :: Layer -> String #

showList :: [Layer] -> ShowS #

Generic Layer Source # 

Associated Types

type Rep Layer :: * -> * #

Methods

from :: Layer -> Rep Layer x #

to :: Rep Layer x -> Layer #

ToJSON Layer Source # 
FromJSON Layer Source # 
type Rep Layer Source # 
type Rep Layer = D1 (MetaData "Layer" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Layer'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_layCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_layWritersCanEditPermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_layStyle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe VectorStyle))) ((:*:) (S1 (MetaSel (Just Symbol "_layEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_layDatasourceType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LayerDatasourceType)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_layPublishingStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LayerPublishingStatus))) (S1 (MetaSel (Just Symbol "_layCreatorEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_layLayerType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LayerLayerType))) ((:*:) (S1 (MetaSel (Just Symbol "_layLastModifiedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_layDatasources") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Datasource]))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_layLastModifierEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_layName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_layBbox") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Double]))) ((:*:) (S1 (MetaSel (Just Symbol "_layProcessingStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LayerProcessingStatus))) (S1 (MetaSel (Just Symbol "_layId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_layProjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_layDraftAccessList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_layPublishedAccessList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_layDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_layTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))))))))

layCreationTime :: Lens' Layer (Maybe UTCTime) Source #

The creation time of this layer. The value is an RFC 3339 formatted date-time value (e.g. 1970-01-01T00:00:00Z).

layWritersCanEditPermissions :: Lens' Layer (Maybe Bool) Source #

If true, WRITERs of the asset are able to edit the asset permissions.

layStyle :: Lens' Layer (Maybe VectorStyle) Source #

The styling information for a vector layer. Note: Style information is returned in response to a get request but not a list request. After requesting a list of layers, you'll need to send a get request to retrieve the VectorStyles for each layer.

layEtag :: Lens' Layer (Maybe Text) Source #

The ETag, used to refer to the current version of the asset.

layDatasourceType :: Lens' Layer (Maybe LayerDatasourceType) Source #

Deprecated: The type of the datasources used to build this Layer. Note: This has been replaced by layerType, but is still available for now to maintain backward compatibility.

layPublishingStatus :: Lens' Layer (Maybe LayerPublishingStatus) Source #

The publishing status of this layer.

layCreatorEmail :: Lens' Layer (Maybe Text) Source #

The email address of the creator of this layer. This is only returned on GET requests and not LIST requests.

layLayerType :: Lens' Layer (Maybe LayerLayerType) Source #

The type of the datasources used to build this Layer. This should be used instead of datasourceType. At least one of layerType and datasourceType and must be specified, but layerType takes precedence.

layLastModifiedTime :: Lens' Layer (Maybe UTCTime) Source #

The last modified time of this layer. The value is an RFC 3339 formatted date-time value (e.g. 1970-01-01T00:00:00Z).

layDatasources :: Lens' Layer [Datasource] Source #

An array of datasources used to build this layer. If layerType is "image", or layerType is not specified and datasourceType is "image", then each element in this array is a reference to an Image or RasterCollection. If layerType is "vector", or layerType is not specified and datasourceType is "table" then each element in this array is a reference to a Vector Table.

layLastModifierEmail :: Lens' Layer (Maybe Text) Source #

The email address of the last modifier of this layer. This is only returned on GET requests and not LIST requests.

layName :: Lens' Layer (Maybe Text) Source #

The name of this Layer, supplied by the author.

layBbox :: Lens' Layer [Double] Source #

A rectangular bounding box which contains all of the data in this Layer. The box is expressed as \"west, south, east, north\". The numbers represent latitude and longitude in decimal degrees.

layProcessingStatus :: Lens' Layer (Maybe LayerProcessingStatus) Source #

The processing status of this layer.

layId :: Lens' Layer (Maybe Text) Source #

A globally unique ID, used to refer to this Layer.

layProjectId :: Lens' Layer (Maybe Text) Source #

The ID of the project that this Layer is in.

layDraftAccessList :: Lens' Layer (Maybe Text) Source #

Deprecated: The name of an access list of the Map Editor type. The user on whose behalf the request is being sent must be an editor on that access list. Note: Google Maps Engine no longer uses access lists. Instead, each asset has its own list of permissions. For backward compatibility, the API still accepts access lists for projects that are already using access lists. If you created a GME account/project after July 14th, 2014, you will not be able to send API requests that include access lists. Note: This is an input field only. It is not returned in response to a list or get request.

layPublishedAccessList :: Lens' Layer (Maybe Text) Source #

Deprecated: The access list to whom view permissions are granted. The value must be the name of a Maps Engine access list of the Map Viewer type, and the user must be a viewer on that list. Note: Google Maps Engine no longer uses access lists. Instead, each asset has its own list of permissions. For backward compatibility, the API still accepts access lists for projects that are already using access lists. If you created a GME account/project after July 14th, 2014, you will not be able to send API requests that include access lists. Note: This is an input field only. It is not returned in response to a list or get request.

layDescription :: Lens' Layer (Maybe Text) Source #

The description of this Layer, supplied by the author.

layTags :: Lens' Layer [Text] Source #

Tags of this Layer.

PointStyle

data PointStyle Source #

Style for points.

See: pointStyle smart constructor.

Instances

Eq PointStyle Source # 
Data PointStyle Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PointStyle -> c PointStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PointStyle #

toConstr :: PointStyle -> Constr #

dataTypeOf :: PointStyle -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PointStyle) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PointStyle) #

gmapT :: (forall b. Data b => b -> b) -> PointStyle -> PointStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PointStyle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PointStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> PointStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PointStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PointStyle -> m PointStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PointStyle -> m PointStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PointStyle -> m PointStyle #

Show PointStyle Source # 
Generic PointStyle Source # 

Associated Types

type Rep PointStyle :: * -> * #

ToJSON PointStyle Source # 
FromJSON PointStyle Source # 
type Rep PointStyle Source # 
type Rep PointStyle = D1 (MetaData "PointStyle" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "PointStyle'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_psIcon") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe IconStyle))) (S1 (MetaSel (Just Symbol "_psLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LabelStyle)))))

pointStyle :: PointStyle Source #

Creates a value of PointStyle with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

psIcon :: Lens' PointStyle (Maybe IconStyle) Source #

Icon for the point; if it isn't null, exactly one of 'name', 'id' or 'scaledShape' must be set.

psLabel :: Lens' PointStyle (Maybe LabelStyle) Source #

Label style for the point.

RasterCollectionsListProcessingStatus

data RasterCollectionsListProcessingStatus Source #

Constructors

RCLPSComplete

complete The raster collection has completed processing.

RCLPSFailed

failed The raster collection has failed processing.

RCLPSNotReady

notReady The raster collection is not ready for processing.

RCLPSProcessing

processing The raster collection is processing.

RCLPSReady

ready The raster collection is ready for processing.

Instances

Enum RasterCollectionsListProcessingStatus Source # 
Eq RasterCollectionsListProcessingStatus Source # 
Data RasterCollectionsListProcessingStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RasterCollectionsListProcessingStatus -> c RasterCollectionsListProcessingStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RasterCollectionsListProcessingStatus #

toConstr :: RasterCollectionsListProcessingStatus -> Constr #

dataTypeOf :: RasterCollectionsListProcessingStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RasterCollectionsListProcessingStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RasterCollectionsListProcessingStatus) #

gmapT :: (forall b. Data b => b -> b) -> RasterCollectionsListProcessingStatus -> RasterCollectionsListProcessingStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RasterCollectionsListProcessingStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RasterCollectionsListProcessingStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> RasterCollectionsListProcessingStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RasterCollectionsListProcessingStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RasterCollectionsListProcessingStatus -> m RasterCollectionsListProcessingStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionsListProcessingStatus -> m RasterCollectionsListProcessingStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionsListProcessingStatus -> m RasterCollectionsListProcessingStatus #

Ord RasterCollectionsListProcessingStatus Source # 
Read RasterCollectionsListProcessingStatus Source # 
Show RasterCollectionsListProcessingStatus Source # 
Generic RasterCollectionsListProcessingStatus Source # 
Hashable RasterCollectionsListProcessingStatus Source # 
ToJSON RasterCollectionsListProcessingStatus Source # 
FromJSON RasterCollectionsListProcessingStatus Source # 
FromHttpApiData RasterCollectionsListProcessingStatus Source # 
ToHttpApiData RasterCollectionsListProcessingStatus Source # 
type Rep RasterCollectionsListProcessingStatus Source # 
type Rep RasterCollectionsListProcessingStatus = D1 (MetaData "RasterCollectionsListProcessingStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "RCLPSComplete" PrefixI False) U1) (C1 (MetaCons "RCLPSFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RCLPSNotReady" PrefixI False) U1) ((:+:) (C1 (MetaCons "RCLPSProcessing" PrefixI False) U1) (C1 (MetaCons "RCLPSReady" PrefixI False) U1))))

Raster

data Raster Source #

A geo-referenced raster.

See: raster smart constructor.

Instances

Eq Raster Source # 

Methods

(==) :: Raster -> Raster -> Bool #

(/=) :: Raster -> Raster -> Bool #

Data Raster Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Raster -> c Raster #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Raster #

toConstr :: Raster -> Constr #

dataTypeOf :: Raster -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Raster) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Raster) #

gmapT :: (forall b. Data b => b -> b) -> Raster -> Raster #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Raster -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Raster -> r #

gmapQ :: (forall d. Data d => d -> u) -> Raster -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Raster -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Raster -> m Raster #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Raster -> m Raster #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Raster -> m Raster #

Show Raster Source # 
Generic Raster Source # 

Associated Types

type Rep Raster :: * -> * #

Methods

from :: Raster -> Rep Raster x #

to :: Rep Raster x -> Raster #

ToJSON Raster Source # 
FromJSON Raster Source # 
type Rep Raster Source # 
type Rep Raster = D1 (MetaData "Raster" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Raster'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rrCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_rrWritersCanEditPermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_rrMaskType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_rrEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rrCreatorEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rrRasterType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RasterRasterType)))) ((:*:) (S1 (MetaSel (Just Symbol "_rrLastModifiedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) ((:*:) (S1 (MetaSel (Just Symbol "_rrLastModifierEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rrAcquisitionTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe AcquisitionTime))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rrName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rrBbox") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Double])))) ((:*:) (S1 (MetaSel (Just Symbol "_rrProcessingStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe RasterProcessingStatus))) ((:*:) (S1 (MetaSel (Just Symbol "_rrFiles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [File]))) (S1 (MetaSel (Just Symbol "_rrId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rrProjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rrDraftAccessList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rrDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rrAttribution") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rrTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))))))))

rrCreationTime :: Lens' Raster (Maybe UTCTime) Source #

The creation time of this raster. The value is an RFC 3339 formatted date-time value (e.g. 1970-01-01T00:00:00Z).

rrWritersCanEditPermissions :: Lens' Raster (Maybe Bool) Source #

If true, WRITERs of the asset are able to edit the asset permissions.

rrMaskType :: Lens' Raster Text Source #

The mask processing type of this Raster.

rrEtag :: Lens' Raster (Maybe Text) Source #

The ETag, used to refer to the current version of the asset.

rrCreatorEmail :: Lens' Raster (Maybe Text) Source #

The email address of the creator of this raster. This is only returned on GET requests and not LIST requests.

rrRasterType :: Lens' Raster (Maybe RasterRasterType) Source #

The type of this Raster. Always "image" today.

rrLastModifiedTime :: Lens' Raster (Maybe UTCTime) Source #

The last modified time of this raster. The value is an RFC 3339 formatted date-time value (e.g. 1970-01-01T00:00:00Z).

rrLastModifierEmail :: Lens' Raster (Maybe Text) Source #

The email address of the last modifier of this raster. This is only returned on GET requests and not LIST requests.

rrAcquisitionTime :: Lens' Raster (Maybe AcquisitionTime) Source #

The acquisition time of this Raster.

rrName :: Lens' Raster (Maybe Text) Source #

The name of this Raster, supplied by the author.

rrBbox :: Lens' Raster [Double] Source #

A rectangular bounding box which contains all of the data in this Raster. The box is expressed as \"west, south, east, north\". The numbers represent latitudes and longitudes in decimal degrees.

rrProcessingStatus :: Lens' Raster (Maybe RasterProcessingStatus) Source #

The processing status of this Raster.

rrFiles :: Lens' Raster [File] Source #

The files associated with this Raster.

rrId :: Lens' Raster (Maybe Text) Source #

A globally unique ID, used to refer to this Raster.

rrProjectId :: Lens' Raster (Maybe Text) Source #

The ID of the project that this Raster is in.

rrDraftAccessList :: Lens' Raster (Maybe Text) Source #

Deprecated: The name of an access list of the Map Editor type. The user on whose behalf the request is being sent must be an editor on that access list. Note: Google Maps Engine no longer uses access lists. Instead, each asset has its own list of permissions. For backward compatibility, the API still accepts access lists for projects that are already using access lists. If you created a GME account/project after July 14th, 2014, you will not be able to send API requests that include access lists. Note: This is an input field only. It is not returned in response to a list or get request.

rrDescription :: Lens' Raster (Maybe Text) Source #

The description of this Raster, supplied by the author.

rrAttribution :: Lens' Raster (Maybe Text) Source #

The name of the attribution to be used for this Raster.

rrTags :: Lens' Raster [Text] Source #

Tags of this Raster.

PolygonStyle

data PolygonStyle Source #

Style for polygons.

See: polygonStyle smart constructor.

Instances

Eq PolygonStyle Source # 
Data PolygonStyle Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PolygonStyle -> c PolygonStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PolygonStyle #

toConstr :: PolygonStyle -> Constr #

dataTypeOf :: PolygonStyle -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PolygonStyle) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PolygonStyle) #

gmapT :: (forall b. Data b => b -> b) -> PolygonStyle -> PolygonStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PolygonStyle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PolygonStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> PolygonStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PolygonStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PolygonStyle -> m PolygonStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PolygonStyle -> m PolygonStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PolygonStyle -> m PolygonStyle #

Show PolygonStyle Source # 
Generic PolygonStyle Source # 

Associated Types

type Rep PolygonStyle :: * -> * #

ToJSON PolygonStyle Source # 
FromJSON PolygonStyle Source # 
type Rep PolygonStyle Source # 
type Rep PolygonStyle = D1 (MetaData "PolygonStyle" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "PolygonStyle'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pStroke") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BOrder))) ((:*:) (S1 (MetaSel (Just Symbol "_pFill") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Color))) (S1 (MetaSel (Just Symbol "_pLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LabelStyle))))))

polygonStyle :: PolygonStyle Source #

Creates a value of PolygonStyle with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

pStroke :: Lens' PolygonStyle (Maybe BOrder) Source #

Border of the polygon. 0 < border.width <= 10.

pFill :: Lens' PolygonStyle (Maybe Color) Source #

Fill color of the polygon. If not provided, the polygon will be transparent and not visible if there is no border.

pLabel :: Lens' PolygonStyle (Maybe LabelStyle) Source #

Label style for the polygon.

Permission

data Permission Source #

A permission defines the user or group that has access to an asset, and the type of access they have.

See: permission smart constructor.

Instances

Eq Permission Source # 
Data Permission Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Permission -> c Permission #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Permission #

toConstr :: Permission -> Constr #

dataTypeOf :: Permission -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Permission) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Permission) #

gmapT :: (forall b. Data b => b -> b) -> Permission -> Permission #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Permission -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Permission -> r #

gmapQ :: (forall d. Data d => d -> u) -> Permission -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Permission -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Permission -> m Permission #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Permission -> m Permission #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Permission -> m Permission #

Show Permission Source # 
Generic Permission Source # 

Associated Types

type Rep Permission :: * -> * #

ToJSON Permission Source # 
FromJSON Permission Source # 
type Rep Permission Source # 
type Rep Permission = D1 (MetaData "Permission" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Permission'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_perRole") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PermissionRole))) (S1 (MetaSel (Just Symbol "_perId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_perType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PermissionType))) (S1 (MetaSel (Just Symbol "_perDiscoverable") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool))))))

permission :: Permission Source #

Creates a value of Permission with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

perRole :: Lens' Permission (Maybe PermissionRole) Source #

The type of access granted to this user or group.

perId :: Lens' Permission (Maybe Text) Source #

The unique identifier of the permission. This could be the email address of the user or group this permission refers to, or the string "anyone" for public permissions.

perDiscoverable :: Lens' Permission (Maybe Bool) Source #

Indicates whether a public asset is listed and can be found via a web search (value true), or is visible only to people who have a link to the asset (value false).

PublishedLayer

data PublishedLayer Source #

The published version of a layer.

See: publishedLayer smart constructor.

Instances

Eq PublishedLayer Source # 
Data PublishedLayer Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PublishedLayer -> c PublishedLayer #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PublishedLayer #

toConstr :: PublishedLayer -> Constr #

dataTypeOf :: PublishedLayer -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PublishedLayer) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublishedLayer) #

gmapT :: (forall b. Data b => b -> b) -> PublishedLayer -> PublishedLayer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PublishedLayer -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PublishedLayer -> r #

gmapQ :: (forall d. Data d => d -> u) -> PublishedLayer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PublishedLayer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PublishedLayer -> m PublishedLayer #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PublishedLayer -> m PublishedLayer #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PublishedLayer -> m PublishedLayer #

Show PublishedLayer Source # 
Generic PublishedLayer Source # 

Associated Types

type Rep PublishedLayer :: * -> * #

ToJSON PublishedLayer Source # 
FromJSON PublishedLayer Source # 
type Rep PublishedLayer Source # 
type Rep PublishedLayer = D1 (MetaData "PublishedLayer" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "PublishedLayer'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_plLayerType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe PublishedLayerLayerType))) (S1 (MetaSel (Just Symbol "_plName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_plId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_plProjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_plDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

publishedLayer :: PublishedLayer Source #

Creates a value of PublishedLayer with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

plLayerType :: Lens' PublishedLayer (Maybe PublishedLayerLayerType) Source #

The type of the datasources used to build this Layer. This should be used instead of datasourceType. At least one of layerType and datasourceType and must be specified, but layerType takes precedence.

plName :: Lens' PublishedLayer (Maybe Text) Source #

The name of this Layer, supplied by the author.

plId :: Lens' PublishedLayer (Maybe Text) Source #

A globally unique ID, used to refer to this Layer.

plProjectId :: Lens' PublishedLayer (Maybe Text) Source #

The ID of the project that this Layer is in.

plDescription :: Lens' PublishedLayer (Maybe Text) Source #

The description of this Layer, supplied by the author.

LayersListRole

data LayersListRole Source #

The role parameter indicates that the response should only contain assets where the current user has the specified level of access.

Constructors

LLROwner

owner The user can read, write and administer the asset.

LLRReader

reader The user can read the asset.

LLRWriter

writer The user can read and write the asset.

Instances

Enum LayersListRole Source # 
Eq LayersListRole Source # 
Data LayersListRole Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LayersListRole -> c LayersListRole #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LayersListRole #

toConstr :: LayersListRole -> Constr #

dataTypeOf :: LayersListRole -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LayersListRole) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LayersListRole) #

gmapT :: (forall b. Data b => b -> b) -> LayersListRole -> LayersListRole #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LayersListRole -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LayersListRole -> r #

gmapQ :: (forall d. Data d => d -> u) -> LayersListRole -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LayersListRole -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LayersListRole -> m LayersListRole #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LayersListRole -> m LayersListRole #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LayersListRole -> m LayersListRole #

Ord LayersListRole Source # 
Read LayersListRole Source # 
Show LayersListRole Source # 
Generic LayersListRole Source # 

Associated Types

type Rep LayersListRole :: * -> * #

Hashable LayersListRole Source # 
ToJSON LayersListRole Source # 
FromJSON LayersListRole Source # 
FromHttpApiData LayersListRole Source # 
ToHttpApiData LayersListRole Source # 
type Rep LayersListRole Source # 
type Rep LayersListRole = D1 (MetaData "LayersListRole" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "LLROwner" PrefixI False) U1) ((:+:) (C1 (MetaCons "LLRReader" PrefixI False) U1) (C1 (MetaCons "LLRWriter" PrefixI False) U1)))

Table

data Table Source #

A collection of geographic features, and associated metadata.

See: table smart constructor.

Instances

Eq Table Source # 

Methods

(==) :: Table -> Table -> Bool #

(/=) :: Table -> Table -> Bool #

Data Table Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Table -> c Table #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Table #

toConstr :: Table -> Constr #

dataTypeOf :: Table -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Table) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Table) #

gmapT :: (forall b. Data b => b -> b) -> Table -> Table #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Table -> r #

gmapQ :: (forall d. Data d => d -> u) -> Table -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Table -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Table -> m Table #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Table -> m Table #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Table -> m Table #

Show Table Source # 

Methods

showsPrec :: Int -> Table -> ShowS #

show :: Table -> String #

showList :: [Table] -> ShowS #

Generic Table Source # 

Associated Types

type Rep Table :: * -> * #

Methods

from :: Table -> Rep Table x #

to :: Rep Table x -> Table #

ToJSON Table Source # 
FromJSON Table Source # 
type Rep Table Source # 
type Rep Table = D1 (MetaData "Table" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "Table'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_tabCreationTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_tabWritersCanEditPermissions") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bool)))) ((:*:) (S1 (MetaSel (Just Symbol "_tabEtag") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tabCreatorEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_tabLastModifiedTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe DateTime'))) (S1 (MetaSel (Just Symbol "_tabSchema") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Schema)))) ((:*:) (S1 (MetaSel (Just Symbol "_tabLastModifierEmail") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_tabName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tabBbox") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Double]))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_tabProcessingStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe TableProcessingStatus))) (S1 (MetaSel (Just Symbol "_tabFiles") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [File])))) ((:*:) (S1 (MetaSel (Just Symbol "_tabId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tabProjectId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_tabDraftAccessList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tabPublishedAccessList") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_tabSourceEncoding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) ((:*:) (S1 (MetaSel (Just Symbol "_tabDescription") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_tabTags") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text])))))))))

tabCreationTime :: Lens' Table (Maybe UTCTime) Source #

The creation time of this table. The value is an RFC 3339 formatted date-time value (e.g. 1970-01-01T00:00:00Z).

tabWritersCanEditPermissions :: Lens' Table (Maybe Bool) Source #

If true, WRITERs of the asset are able to edit the asset permissions.

tabEtag :: Lens' Table (Maybe Text) Source #

The ETag, used to refer to the current version of the asset.

tabCreatorEmail :: Lens' Table (Maybe Text) Source #

The email address of the creator of this table. This is only returned on GET requests and not LIST requests.

tabLastModifiedTime :: Lens' Table (Maybe UTCTime) Source #

The last modified time of this table. The value is an RFC 3339 formatted date-time value (e.g. 1970-01-01T00:00:00Z).

tabSchema :: Lens' Table (Maybe Schema) Source #

The schema for this table. Note: The schema is returned in response to a get request but not a list request. After requesting a list of tables, you'll need to send a get request to retrieve the schema for each table.

tabLastModifierEmail :: Lens' Table (Maybe Text) Source #

The email address of the last modifier of this table. This is only returned on GET requests and not LIST requests.

tabName :: Lens' Table (Maybe Text) Source #

The name of this table, supplied by the author.

tabBbox :: Lens' Table [Double] Source #

A rectangular bounding box which contains all of the data in this Table. The box is expressed as \"west, south, east, north\". The numbers represent latitude and longitude in decimal degrees.

tabProcessingStatus :: Lens' Table (Maybe TableProcessingStatus) Source #

The processing status of this table.

tabFiles :: Lens' Table [File] Source #

The files associated with this table.

tabId :: Lens' Table (Maybe Text) Source #

A globally unique ID, used to refer to this table.

tabProjectId :: Lens' Table (Maybe Text) Source #

The ID of the project to which the table belongs.

tabDraftAccessList :: Lens' Table (Maybe Text) Source #

Deprecated: The name of an access list of the Map Editor type. The user on whose behalf the request is being sent must be an editor on that access list. Note: Google Maps Engine no longer uses access lists. Instead, each asset has its own list of permissions. For backward compatibility, the API still accepts access lists for projects that are already using access lists. If you created a GME account/project after July 14th, 2014, you will not be able to send API requests that include access lists. Note: This is an input field only. It is not returned in response to a list or get request.

tabPublishedAccessList :: Lens' Table (Maybe Text) Source #

Deprecated: The access list to whom view permissions are granted. The value must be the name of a Maps Engine access list of the Map Viewer type, and the user must be a viewer on that list. Note: Google Maps Engine no longer uses access lists. Instead, each asset has its own list of permissions. For backward compatibility, the API still accepts access lists for projects that are already using access lists. If you created a GME account/project after July 14th, 2014, you will not be able to send API requests that include access lists. Note: This is an input field only. It is not returned in response to a list or get request.

tabSourceEncoding :: Lens' Table Text Source #

Encoding of the uploaded files. Valid values include UTF-8, CP1251, ISO 8859-1, and Shift_JIS.

tabDescription :: Lens' Table (Maybe Text) Source #

The description of this table, supplied by the author.

tabTags :: Lens' Table [Text] Source #

An array of text strings, with each string representing a tag. More information about tags can be found in the Tagging data article of the Maps Engine help center.

File

data File Source #

A single File, which is a component of an Asset.

See: file smart constructor.

Instances

Eq File Source # 

Methods

(==) :: File -> File -> Bool #

(/=) :: File -> File -> Bool #

Data File Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> File -> c File #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c File #

toConstr :: File -> Constr #

dataTypeOf :: File -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c File) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c File) #

gmapT :: (forall b. Data b => b -> b) -> File -> File #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> File -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> File -> r #

gmapQ :: (forall d. Data d => d -> u) -> File -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> File -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> File -> m File #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> File -> m File #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> File -> m File #

Show File Source # 

Methods

showsPrec :: Int -> File -> ShowS #

show :: File -> String #

showList :: [File] -> ShowS #

Generic File Source # 

Associated Types

type Rep File :: * -> * #

Methods

from :: File -> Rep File x #

to :: Rep File x -> File #

ToJSON File Source # 
FromJSON File Source # 
type Rep File Source # 
type Rep File = D1 (MetaData "File" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "File'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) ((:*:) (S1 (MetaSel (Just Symbol "_fUploadStatus") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FileUploadStatus))) (S1 (MetaSel (Just Symbol "_fFilename") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

file :: File Source #

Creates a value of File with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

fSize :: Lens' File (Maybe Int64) Source #

The size of the file in bytes.

fUploadStatus :: Lens' File (Maybe FileUploadStatus) Source #

The upload status of the file.

fFilename :: Lens' File (Maybe Text) Source #

The name of the file.

VectorStyle

data VectorStyle Source #

A vector style contains styling information for vector layer.

See: vectorStyle smart constructor.

Instances

Eq VectorStyle Source # 
Data VectorStyle Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> VectorStyle -> c VectorStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c VectorStyle #

toConstr :: VectorStyle -> Constr #

dataTypeOf :: VectorStyle -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c VectorStyle) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c VectorStyle) #

gmapT :: (forall b. Data b => b -> b) -> VectorStyle -> VectorStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> VectorStyle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> VectorStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> VectorStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> VectorStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> VectorStyle -> m VectorStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> VectorStyle -> m VectorStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> VectorStyle -> m VectorStyle #

Show VectorStyle Source # 
Generic VectorStyle Source # 

Associated Types

type Rep VectorStyle :: * -> * #

ToJSON VectorStyle Source # 
FromJSON VectorStyle Source # 
type Rep VectorStyle Source # 
type Rep VectorStyle = D1 (MetaData "VectorStyle" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "VectorStyle'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_vsDisplayRules") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [DisplayRule]))) ((:*:) (S1 (MetaSel (Just Symbol "_vsFeatureInfo") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FeatureInfo))) (S1 (MetaSel (Just Symbol "_vsType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe VectorStyleType))))))

vectorStyle :: VectorStyle Source #

Creates a value of VectorStyle with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

vsFeatureInfo :: Lens' VectorStyle (Maybe FeatureInfo) Source #

Individual feature info, this is called Info Window in Maps Engine UI. If not provided, a default template with all attributes will be generated.

vsType :: Lens' VectorStyle (Maybe VectorStyleType) Source #

The type of the vector style. Currently, only displayRule is supported.

PermissionsBatchDeleteResponse

data PermissionsBatchDeleteResponse Source #

The response returned by a call to mapsengine.permissions.batchDelete.

See: permissionsBatchDeleteResponse smart constructor.

Instances

Eq PermissionsBatchDeleteResponse Source # 
Data PermissionsBatchDeleteResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PermissionsBatchDeleteResponse -> c PermissionsBatchDeleteResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PermissionsBatchDeleteResponse #

toConstr :: PermissionsBatchDeleteResponse -> Constr #

dataTypeOf :: PermissionsBatchDeleteResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PermissionsBatchDeleteResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PermissionsBatchDeleteResponse) #

gmapT :: (forall b. Data b => b -> b) -> PermissionsBatchDeleteResponse -> PermissionsBatchDeleteResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PermissionsBatchDeleteResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PermissionsBatchDeleteResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> PermissionsBatchDeleteResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PermissionsBatchDeleteResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PermissionsBatchDeleteResponse -> m PermissionsBatchDeleteResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PermissionsBatchDeleteResponse -> m PermissionsBatchDeleteResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PermissionsBatchDeleteResponse -> m PermissionsBatchDeleteResponse #

Show PermissionsBatchDeleteResponse Source # 
Generic PermissionsBatchDeleteResponse Source # 
ToJSON PermissionsBatchDeleteResponse Source # 
FromJSON PermissionsBatchDeleteResponse Source # 
type Rep PermissionsBatchDeleteResponse Source # 
type Rep PermissionsBatchDeleteResponse = D1 (MetaData "PermissionsBatchDeleteResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "PermissionsBatchDeleteResponse'" PrefixI False) U1)

permissionsBatchDeleteResponse :: PermissionsBatchDeleteResponse Source #

Creates a value of PermissionsBatchDeleteResponse with the minimum fields required to make a request.

TablesFeaturesGetVersion

data TablesFeaturesGetVersion Source #

The table version to access. See Accessing Public Data for information.

Constructors

TFGVDraft

draft The draft version.

TFGVPublished

published The published version.

Instances

Enum TablesFeaturesGetVersion Source # 
Eq TablesFeaturesGetVersion Source # 
Data TablesFeaturesGetVersion Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TablesFeaturesGetVersion -> c TablesFeaturesGetVersion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TablesFeaturesGetVersion #

toConstr :: TablesFeaturesGetVersion -> Constr #

dataTypeOf :: TablesFeaturesGetVersion -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TablesFeaturesGetVersion) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TablesFeaturesGetVersion) #

gmapT :: (forall b. Data b => b -> b) -> TablesFeaturesGetVersion -> TablesFeaturesGetVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TablesFeaturesGetVersion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TablesFeaturesGetVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> TablesFeaturesGetVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TablesFeaturesGetVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TablesFeaturesGetVersion -> m TablesFeaturesGetVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TablesFeaturesGetVersion -> m TablesFeaturesGetVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TablesFeaturesGetVersion -> m TablesFeaturesGetVersion #

Ord TablesFeaturesGetVersion Source # 
Read TablesFeaturesGetVersion Source # 
Show TablesFeaturesGetVersion Source # 
Generic TablesFeaturesGetVersion Source # 
Hashable TablesFeaturesGetVersion Source # 
ToJSON TablesFeaturesGetVersion Source # 
FromJSON TablesFeaturesGetVersion Source # 
FromHttpApiData TablesFeaturesGetVersion Source # 
ToHttpApiData TablesFeaturesGetVersion Source # 
type Rep TablesFeaturesGetVersion Source # 
type Rep TablesFeaturesGetVersion = D1 (MetaData "TablesFeaturesGetVersion" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "TFGVDraft" PrefixI False) U1) (C1 (MetaCons "TFGVPublished" PrefixI False) U1))

MapKmlLink

data MapKmlLink Source #

mapKmlLink :: MapKmlLink Source #

Creates a value of MapKmlLink with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

mklDefaultViewport :: Lens' MapKmlLink [Double] Source #

An array of four numbers (west, south, east, north) which defines the rectangular bounding box of the default viewport. The numbers represent latitude and longitude in decimal degrees.

mklVisibility :: Lens' MapKmlLink (Maybe Text) Source #

The visibility setting of this MapKmlLink. One of "defaultOn" or "defaultOff".

mklName :: Lens' MapKmlLink (Maybe Text) Source #

The name of this MapKmlLink.

mklType :: Lens' MapKmlLink (Maybe MapKmlLinkType) Source #

Identifies this object as a MapKmlLink.

mklKmlURL :: Lens' MapKmlLink (Maybe Text) Source #

The URL to the KML file represented by this MapKmlLink.

RasterCollectionRasterType

data RasterCollectionRasterType Source #

The type of rasters contained within this RasterCollection.

Constructors

RCRTImage
image

Instances

Enum RasterCollectionRasterType Source # 
Eq RasterCollectionRasterType Source # 
Data RasterCollectionRasterType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RasterCollectionRasterType -> c RasterCollectionRasterType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RasterCollectionRasterType #

toConstr :: RasterCollectionRasterType -> Constr #

dataTypeOf :: RasterCollectionRasterType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RasterCollectionRasterType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RasterCollectionRasterType) #

gmapT :: (forall b. Data b => b -> b) -> RasterCollectionRasterType -> RasterCollectionRasterType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RasterCollectionRasterType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RasterCollectionRasterType -> r #

gmapQ :: (forall d. Data d => d -> u) -> RasterCollectionRasterType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RasterCollectionRasterType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RasterCollectionRasterType -> m RasterCollectionRasterType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionRasterType -> m RasterCollectionRasterType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RasterCollectionRasterType -> m RasterCollectionRasterType #

Ord RasterCollectionRasterType Source # 
Read RasterCollectionRasterType Source # 
Show RasterCollectionRasterType Source # 
Generic RasterCollectionRasterType Source # 
Hashable RasterCollectionRasterType Source # 
ToJSON RasterCollectionRasterType Source # 
FromJSON RasterCollectionRasterType Source # 
FromHttpApiData RasterCollectionRasterType Source # 
ToHttpApiData RasterCollectionRasterType Source # 
type Rep RasterCollectionRasterType Source # 
type Rep RasterCollectionRasterType = D1 (MetaData "RasterCollectionRasterType" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "RCRTImage" PrefixI False) U1)

RastersListRole

data RastersListRole Source #

The role parameter indicates that the response should only contain assets where the current user has the specified level of access.

Constructors

RLROwner

owner The user can read, write and administer the asset.

RLRReader

reader The user can read the asset.

RLRWriter

writer The user can read and write the asset.

Instances

Enum RastersListRole Source # 
Eq RastersListRole Source # 
Data RastersListRole Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RastersListRole -> c RastersListRole #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RastersListRole #

toConstr :: RastersListRole -> Constr #

dataTypeOf :: RastersListRole -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RastersListRole) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RastersListRole) #

gmapT :: (forall b. Data b => b -> b) -> RastersListRole -> RastersListRole #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RastersListRole -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RastersListRole -> r #

gmapQ :: (forall d. Data d => d -> u) -> RastersListRole -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RastersListRole -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RastersListRole -> m RastersListRole #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RastersListRole -> m RastersListRole #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RastersListRole -> m RastersListRole #

Ord RastersListRole Source # 
Read RastersListRole Source # 
Show RastersListRole Source # 
Generic RastersListRole Source # 
Hashable RastersListRole Source # 
ToJSON RastersListRole Source # 
FromJSON RastersListRole Source # 
FromHttpApiData RastersListRole Source # 
ToHttpApiData RastersListRole Source # 
type Rep RastersListRole Source # 
type Rep RastersListRole = D1 (MetaData "RastersListRole" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "RLROwner" PrefixI False) U1) ((:+:) (C1 (MetaCons "RLRReader" PrefixI False) U1) (C1 (MetaCons "RLRWriter" PrefixI False) U1)))

PermissionsBatchUpdateResponse

data PermissionsBatchUpdateResponse Source #

The response returned by a call to mapsengine.permissions.batchUpdate.

See: permissionsBatchUpdateResponse smart constructor.

Instances

Eq PermissionsBatchUpdateResponse Source # 
Data PermissionsBatchUpdateResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PermissionsBatchUpdateResponse -> c PermissionsBatchUpdateResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PermissionsBatchUpdateResponse #

toConstr :: PermissionsBatchUpdateResponse -> Constr #

dataTypeOf :: PermissionsBatchUpdateResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PermissionsBatchUpdateResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PermissionsBatchUpdateResponse) #

gmapT :: (forall b. Data b => b -> b) -> PermissionsBatchUpdateResponse -> PermissionsBatchUpdateResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PermissionsBatchUpdateResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PermissionsBatchUpdateResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> PermissionsBatchUpdateResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PermissionsBatchUpdateResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PermissionsBatchUpdateResponse -> m PermissionsBatchUpdateResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PermissionsBatchUpdateResponse -> m PermissionsBatchUpdateResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PermissionsBatchUpdateResponse -> m PermissionsBatchUpdateResponse #

Show PermissionsBatchUpdateResponse Source # 
Generic PermissionsBatchUpdateResponse Source # 
ToJSON PermissionsBatchUpdateResponse Source # 
FromJSON PermissionsBatchUpdateResponse Source # 
type Rep PermissionsBatchUpdateResponse Source # 
type Rep PermissionsBatchUpdateResponse = D1 (MetaData "PermissionsBatchUpdateResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "PermissionsBatchUpdateResponse'" PrefixI False) U1)

permissionsBatchUpdateResponse :: PermissionsBatchUpdateResponse Source #

Creates a value of PermissionsBatchUpdateResponse with the minimum fields required to make a request.

GeoJSONLineString

data GeoJSONLineString Source #

Instances

Eq GeoJSONLineString Source # 
Data GeoJSONLineString Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeoJSONLineString -> c GeoJSONLineString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeoJSONLineString #

toConstr :: GeoJSONLineString -> Constr #

dataTypeOf :: GeoJSONLineString -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GeoJSONLineString) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeoJSONLineString) #

gmapT :: (forall b. Data b => b -> b) -> GeoJSONLineString -> GeoJSONLineString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONLineString -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONLineString -> r #

gmapQ :: (forall d. Data d => d -> u) -> GeoJSONLineString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GeoJSONLineString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GeoJSONLineString -> m GeoJSONLineString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONLineString -> m GeoJSONLineString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONLineString -> m GeoJSONLineString #

Show GeoJSONLineString Source # 
Generic GeoJSONLineString Source # 
ToJSON GeoJSONLineString Source # 
FromJSON GeoJSONLineString Source # 
type Rep GeoJSONLineString Source # 
type Rep GeoJSONLineString = D1 (MetaData "GeoJSONLineString" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "GeoJSONLineString'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gjlsCoordinates") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [[Textual Double]]))) (S1 (MetaSel (Just Symbol "_gjlsType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GeoJSONLineStringType)))))

geoJSONLineString :: GeoJSONLineString Source #

Creates a value of GeoJSONLineString with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gjlsCoordinates :: Lens' GeoJSONLineString [[Double]] Source #

An array of two or more positions, representing a line.

gjlsType :: Lens' GeoJSONLineString (Maybe GeoJSONLineStringType) Source #

Identifies this object as a GeoJsonLineString.

PublishedMapsListResponse

data PublishedMapsListResponse Source #

The response returned by a call to maps.List.published.

See: publishedMapsListResponse smart constructor.

Instances

Eq PublishedMapsListResponse Source # 
Data PublishedMapsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PublishedMapsListResponse -> c PublishedMapsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PublishedMapsListResponse #

toConstr :: PublishedMapsListResponse -> Constr #

dataTypeOf :: PublishedMapsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PublishedMapsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublishedMapsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> PublishedMapsListResponse -> PublishedMapsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PublishedMapsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PublishedMapsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> PublishedMapsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PublishedMapsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PublishedMapsListResponse -> m PublishedMapsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PublishedMapsListResponse -> m PublishedMapsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PublishedMapsListResponse -> m PublishedMapsListResponse #

Show PublishedMapsListResponse Source # 
Generic PublishedMapsListResponse Source # 
ToJSON PublishedMapsListResponse Source # 
FromJSON PublishedMapsListResponse Source # 
type Rep PublishedMapsListResponse Source # 
type Rep PublishedMapsListResponse = D1 (MetaData "PublishedMapsListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "PublishedMapsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pmlrMaps") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PublishedMap]))) (S1 (MetaSel (Just Symbol "_pmlrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bytes)))))

publishedMapsListResponse :: PublishedMapsListResponse Source #

Creates a value of PublishedMapsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

MapsListResponse

data MapsListResponse Source #

The response returned by a call to maps.List.

See: mapsListResponse smart constructor.

Instances

Eq MapsListResponse Source # 
Data MapsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MapsListResponse -> c MapsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MapsListResponse #

toConstr :: MapsListResponse -> Constr #

dataTypeOf :: MapsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MapsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MapsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> MapsListResponse -> MapsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MapsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MapsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> MapsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MapsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MapsListResponse -> m MapsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MapsListResponse -> m MapsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MapsListResponse -> m MapsListResponse #

Show MapsListResponse Source # 
Generic MapsListResponse Source # 
ToJSON MapsListResponse Source # 
FromJSON MapsListResponse Source # 
type Rep MapsListResponse Source # 
type Rep MapsListResponse = D1 (MetaData "MapsListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "MapsListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_mlrMaps") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Map]))) (S1 (MetaSel (Just Symbol "_mlrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bytes)))))

mapsListResponse :: MapsListResponse Source #

Creates a value of MapsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

mlrMaps :: Lens' MapsListResponse [Map] Source #

Resources returned.

MapPublishingStatus

data MapPublishingStatus Source #

The publishing status of this map.

Constructors

MPSNotPublished
notPublished
MPSPublished
published

Instances

Enum MapPublishingStatus Source # 
Eq MapPublishingStatus Source # 
Data MapPublishingStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MapPublishingStatus -> c MapPublishingStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MapPublishingStatus #

toConstr :: MapPublishingStatus -> Constr #

dataTypeOf :: MapPublishingStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MapPublishingStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MapPublishingStatus) #

gmapT :: (forall b. Data b => b -> b) -> MapPublishingStatus -> MapPublishingStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MapPublishingStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MapPublishingStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> MapPublishingStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MapPublishingStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MapPublishingStatus -> m MapPublishingStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MapPublishingStatus -> m MapPublishingStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MapPublishingStatus -> m MapPublishingStatus #

Ord MapPublishingStatus Source # 
Read MapPublishingStatus Source # 
Show MapPublishingStatus Source # 
Generic MapPublishingStatus Source # 
Hashable MapPublishingStatus Source # 
ToJSON MapPublishingStatus Source # 
FromJSON MapPublishingStatus Source # 
FromHttpApiData MapPublishingStatus Source # 
ToHttpApiData MapPublishingStatus Source # 
type Rep MapPublishingStatus Source # 
type Rep MapPublishingStatus = D1 (MetaData "MapPublishingStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "MPSNotPublished" PrefixI False) U1) (C1 (MetaCons "MPSPublished" PrefixI False) U1))

GeoJSONGeometryCollection

data GeoJSONGeometryCollection Source #

A heterogenous collection of GeoJsonGeometry objects.

See: geoJSONGeometryCollection smart constructor.

Instances

Eq GeoJSONGeometryCollection Source # 
Data GeoJSONGeometryCollection Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeoJSONGeometryCollection -> c GeoJSONGeometryCollection #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeoJSONGeometryCollection #

toConstr :: GeoJSONGeometryCollection -> Constr #

dataTypeOf :: GeoJSONGeometryCollection -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GeoJSONGeometryCollection) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeoJSONGeometryCollection) #

gmapT :: (forall b. Data b => b -> b) -> GeoJSONGeometryCollection -> GeoJSONGeometryCollection #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONGeometryCollection -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONGeometryCollection -> r #

gmapQ :: (forall d. Data d => d -> u) -> GeoJSONGeometryCollection -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GeoJSONGeometryCollection -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GeoJSONGeometryCollection -> m GeoJSONGeometryCollection #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONGeometryCollection -> m GeoJSONGeometryCollection #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONGeometryCollection -> m GeoJSONGeometryCollection #

Show GeoJSONGeometryCollection Source # 
Generic GeoJSONGeometryCollection Source # 
ToJSON GeoJSONGeometryCollection Source # 
FromJSON GeoJSONGeometryCollection Source # 
type Rep GeoJSONGeometryCollection Source # 
type Rep GeoJSONGeometryCollection = D1 (MetaData "GeoJSONGeometryCollection" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "GeoJSONGeometryCollection'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gjgcGeometries") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [GeoJSONGeometry]))) (S1 (MetaSel (Just Symbol "_gjgcType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GeoJSONGeometryCollectionType)))))

geoJSONGeometryCollection :: GeoJSONGeometryCollection Source #

Creates a value of GeoJSONGeometryCollection with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gjgcGeometries :: Lens' GeoJSONGeometryCollection [GeoJSONGeometry] Source #

An array of geometry objects. There must be at least 2 different types of geometries in the array.

gjgcType :: Lens' GeoJSONGeometryCollection (Maybe GeoJSONGeometryCollectionType) Source #

Identifies this object as a GeoJsonGeometryCollection.

GeoJSONPolygon

data GeoJSONPolygon Source #

Instances

Eq GeoJSONPolygon Source # 
Data GeoJSONPolygon Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeoJSONPolygon -> c GeoJSONPolygon #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeoJSONPolygon #

toConstr :: GeoJSONPolygon -> Constr #

dataTypeOf :: GeoJSONPolygon -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GeoJSONPolygon) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeoJSONPolygon) #

gmapT :: (forall b. Data b => b -> b) -> GeoJSONPolygon -> GeoJSONPolygon #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONPolygon -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONPolygon -> r #

gmapQ :: (forall d. Data d => d -> u) -> GeoJSONPolygon -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GeoJSONPolygon -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GeoJSONPolygon -> m GeoJSONPolygon #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONPolygon -> m GeoJSONPolygon #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONPolygon -> m GeoJSONPolygon #

Show GeoJSONPolygon Source # 
Generic GeoJSONPolygon Source # 

Associated Types

type Rep GeoJSONPolygon :: * -> * #

ToJSON GeoJSONPolygon Source # 
FromJSON GeoJSONPolygon Source # 
type Rep GeoJSONPolygon Source # 
type Rep GeoJSONPolygon = D1 (MetaData "GeoJSONPolygon" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "GeoJSONPolygon'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gjpCoordinates") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [[[Textual Double]]]))) (S1 (MetaSel (Just Symbol "_gjpType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GeoJSONPolygonType)))))

geoJSONPolygon :: GeoJSONPolygon Source #

Creates a value of GeoJSONPolygon with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gjpCoordinates :: Lens' GeoJSONPolygon [[[Double]]] Source #

An array of LinearRings. A LinearRing is a GeoJsonLineString which is closed (that is, the first and last GeoJsonPositions are equal), and which contains at least four GeoJsonPositions. For polygons with multiple rings, the first LinearRing is the exterior ring, and any subsequent rings are interior rings (that is, holes).

gjpType :: Lens' GeoJSONPolygon (Maybe GeoJSONPolygonType) Source #

Identifies this object as a GeoJsonPolygon.

GeoJSONPoint

data GeoJSONPoint Source #

Instances

Eq GeoJSONPoint Source # 
Data GeoJSONPoint Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> GeoJSONPoint -> c GeoJSONPoint #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c GeoJSONPoint #

toConstr :: GeoJSONPoint -> Constr #

dataTypeOf :: GeoJSONPoint -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c GeoJSONPoint) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c GeoJSONPoint) #

gmapT :: (forall b. Data b => b -> b) -> GeoJSONPoint -> GeoJSONPoint #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONPoint -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> GeoJSONPoint -> r #

gmapQ :: (forall d. Data d => d -> u) -> GeoJSONPoint -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> GeoJSONPoint -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> GeoJSONPoint -> m GeoJSONPoint #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONPoint -> m GeoJSONPoint #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> GeoJSONPoint -> m GeoJSONPoint #

Show GeoJSONPoint Source # 
Generic GeoJSONPoint Source # 

Associated Types

type Rep GeoJSONPoint :: * -> * #

ToJSON GeoJSONPoint Source # 
FromJSON GeoJSONPoint Source # 
type Rep GeoJSONPoint Source # 
type Rep GeoJSONPoint = D1 (MetaData "GeoJSONPoint" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "GeoJSONPoint'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_gjsonpCoordinates") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Double]))) (S1 (MetaSel (Just Symbol "_gjsonpType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe GeoJSONPointType)))))

geoJSONPoint :: GeoJSONPoint Source #

Creates a value of GeoJSONPoint with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

gjsonpCoordinates :: Lens' GeoJSONPoint [Double] Source #

A single GeoJsonPosition, specifying the location of the point.

gjsonpType :: Lens' GeoJSONPoint (Maybe GeoJSONPointType) Source #

Identifies this object as a GeoJsonPoint.

LayersListResponse

data LayersListResponse Source #

The response returned by a call to layers.List. Note: The list response does not include all the fields available in a layer. Refer to the layer resource description for details of the fields that are not included. You'll need to send a get request to retrieve the additional fields for each layer.

See: layersListResponse smart constructor.

Instances

Eq LayersListResponse Source # 
Data LayersListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LayersListResponse -> c LayersListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LayersListResponse #

toConstr :: LayersListResponse -> Constr #

dataTypeOf :: LayersListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LayersListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LayersListResponse) #

gmapT :: (forall b. Data b => b -> b) -> LayersListResponse -> LayersListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LayersListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LayersListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> LayersListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LayersListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LayersListResponse -> m LayersListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LayersListResponse -> m LayersListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LayersListResponse -> m LayersListResponse #

Show LayersListResponse Source # 
Generic LayersListResponse Source # 
ToJSON LayersListResponse Source # 
FromJSON LayersListResponse Source # 
type Rep LayersListResponse Source # 
type Rep LayersListResponse = D1 (MetaData "LayersListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "LayersListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_llrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bytes))) (S1 (MetaSel (Just Symbol "_llrLayers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Layer])))))

layersListResponse :: LayersListResponse Source #

Creates a value of LayersListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

RastersListResponse

data RastersListResponse Source #

The response returned by a call to rasters.List.

See: rastersListResponse smart constructor.

Instances

Eq RastersListResponse Source # 
Data RastersListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RastersListResponse -> c RastersListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c RastersListResponse #

toConstr :: RastersListResponse -> Constr #

dataTypeOf :: RastersListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c RastersListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c RastersListResponse) #

gmapT :: (forall b. Data b => b -> b) -> RastersListResponse -> RastersListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RastersListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RastersListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> RastersListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RastersListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RastersListResponse -> m RastersListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RastersListResponse -> m RastersListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RastersListResponse -> m RastersListResponse #

Show RastersListResponse Source # 
Generic RastersListResponse Source # 
ToJSON RastersListResponse Source # 
FromJSON RastersListResponse Source # 
type Rep RastersListResponse Source # 
type Rep RastersListResponse = D1 (MetaData "RastersListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "RastersListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rlrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rlrRasters") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Raster])))))

rastersListResponse :: RastersListResponse Source #

Creates a value of RastersListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

FileUploadStatus

data FileUploadStatus Source #

The upload status of the file.

Constructors

FUSCanceled
canceled
FUSComplete
complete
FUSFailed
failed
FUSInProgress
inProgress

Instances

Enum FileUploadStatus Source # 
Eq FileUploadStatus Source # 
Data FileUploadStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FileUploadStatus -> c FileUploadStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FileUploadStatus #

toConstr :: FileUploadStatus -> Constr #

dataTypeOf :: FileUploadStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FileUploadStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FileUploadStatus) #

gmapT :: (forall b. Data b => b -> b) -> FileUploadStatus -> FileUploadStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FileUploadStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FileUploadStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> FileUploadStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FileUploadStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FileUploadStatus -> m FileUploadStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FileUploadStatus -> m FileUploadStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FileUploadStatus -> m FileUploadStatus #

Ord FileUploadStatus Source # 
Read FileUploadStatus Source # 
Show FileUploadStatus Source # 
Generic FileUploadStatus Source # 
Hashable FileUploadStatus Source # 
ToJSON FileUploadStatus Source # 
FromJSON FileUploadStatus Source # 
FromHttpApiData FileUploadStatus Source # 
ToHttpApiData FileUploadStatus Source # 
type Rep FileUploadStatus Source # 
type Rep FileUploadStatus = D1 (MetaData "FileUploadStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "FUSCanceled" PrefixI False) U1) (C1 (MetaCons "FUSComplete" PrefixI False) U1)) ((:+:) (C1 (MetaCons "FUSFailed" PrefixI False) U1) (C1 (MetaCons "FUSInProgress" PrefixI False) U1)))

MapsListRole

data MapsListRole Source #

The role parameter indicates that the response should only contain assets where the current user has the specified level of access.

Constructors

MLROwner

owner The user can read, write and administer the asset.

MLRReader

reader The user can read the asset.

MLRWriter

writer The user can read and write the asset.

Instances

Enum MapsListRole Source # 
Eq MapsListRole Source # 
Data MapsListRole Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MapsListRole -> c MapsListRole #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MapsListRole #

toConstr :: MapsListRole -> Constr #

dataTypeOf :: MapsListRole -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MapsListRole) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MapsListRole) #

gmapT :: (forall b. Data b => b -> b) -> MapsListRole -> MapsListRole #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MapsListRole -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MapsListRole -> r #

gmapQ :: (forall d. Data d => d -> u) -> MapsListRole -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MapsListRole -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MapsListRole -> m MapsListRole #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MapsListRole -> m MapsListRole #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MapsListRole -> m MapsListRole #

Ord MapsListRole Source # 
Read MapsListRole Source # 
Show MapsListRole Source # 
Generic MapsListRole Source # 

Associated Types

type Rep MapsListRole :: * -> * #

Hashable MapsListRole Source # 
ToJSON MapsListRole Source # 
FromJSON MapsListRole Source # 
FromHttpApiData MapsListRole Source # 
ToHttpApiData MapsListRole Source # 
type Rep MapsListRole Source # 
type Rep MapsListRole = D1 (MetaData "MapsListRole" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "MLROwner" PrefixI False) U1) ((:+:) (C1 (MetaCons "MLRReader" PrefixI False) U1) (C1 (MetaCons "MLRWriter" PrefixI False) U1)))

TablesGetVersion

data TablesGetVersion Source #

Constructors

TGVDraft

draft The draft version.

TGVPublished

published The published version.

Instances

Enum TablesGetVersion Source # 
Eq TablesGetVersion Source # 
Data TablesGetVersion Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TablesGetVersion -> c TablesGetVersion #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TablesGetVersion #

toConstr :: TablesGetVersion -> Constr #

dataTypeOf :: TablesGetVersion -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TablesGetVersion) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TablesGetVersion) #

gmapT :: (forall b. Data b => b -> b) -> TablesGetVersion -> TablesGetVersion #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TablesGetVersion -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TablesGetVersion -> r #

gmapQ :: (forall d. Data d => d -> u) -> TablesGetVersion -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TablesGetVersion -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TablesGetVersion -> m TablesGetVersion #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TablesGetVersion -> m TablesGetVersion #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TablesGetVersion -> m TablesGetVersion #

Ord TablesGetVersion Source # 
Read TablesGetVersion Source # 
Show TablesGetVersion Source # 
Generic TablesGetVersion Source # 
Hashable TablesGetVersion Source # 
ToJSON TablesGetVersion Source # 
FromJSON TablesGetVersion Source # 
FromHttpApiData TablesGetVersion Source # 
ToHttpApiData TablesGetVersion Source # 
type Rep TablesGetVersion Source # 
type Rep TablesGetVersion = D1 (MetaData "TablesGetVersion" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) (C1 (MetaCons "TGVDraft" PrefixI False) U1) (C1 (MetaCons "TGVPublished" PrefixI False) U1))

PermissionsListResponse

data PermissionsListResponse Source #

Instances

Eq PermissionsListResponse Source # 
Data PermissionsListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PermissionsListResponse -> c PermissionsListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PermissionsListResponse #

toConstr :: PermissionsListResponse -> Constr #

dataTypeOf :: PermissionsListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PermissionsListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PermissionsListResponse) #

gmapT :: (forall b. Data b => b -> b) -> PermissionsListResponse -> PermissionsListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PermissionsListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PermissionsListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> PermissionsListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PermissionsListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PermissionsListResponse -> m PermissionsListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PermissionsListResponse -> m PermissionsListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PermissionsListResponse -> m PermissionsListResponse #

Show PermissionsListResponse Source # 
Generic PermissionsListResponse Source # 
ToJSON PermissionsListResponse Source # 
FromJSON PermissionsListResponse Source # 
type Rep PermissionsListResponse Source # 
type Rep PermissionsListResponse = D1 (MetaData "PermissionsListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" True) (C1 (MetaCons "PermissionsListResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_plrPermissions") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Permission]))))

permissionsListResponse :: PermissionsListResponse Source #

Creates a value of PermissionsListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

plrPermissions :: Lens' PermissionsListResponse [Permission] Source #

The set of permissions associated with this asset.

TableProcessingStatus

data TableProcessingStatus Source #

The processing status of this table.

Constructors

TPSComplete
complete
TPSFailed
failed
TPSNotReady
notReady
TPSProcessing
processing
TPSReady
ready

Instances

Enum TableProcessingStatus Source # 
Eq TableProcessingStatus Source # 
Data TableProcessingStatus Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TableProcessingStatus -> c TableProcessingStatus #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TableProcessingStatus #

toConstr :: TableProcessingStatus -> Constr #

dataTypeOf :: TableProcessingStatus -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TableProcessingStatus) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TableProcessingStatus) #

gmapT :: (forall b. Data b => b -> b) -> TableProcessingStatus -> TableProcessingStatus #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TableProcessingStatus -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TableProcessingStatus -> r #

gmapQ :: (forall d. Data d => d -> u) -> TableProcessingStatus -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TableProcessingStatus -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TableProcessingStatus -> m TableProcessingStatus #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TableProcessingStatus -> m TableProcessingStatus #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TableProcessingStatus -> m TableProcessingStatus #

Ord TableProcessingStatus Source # 
Read TableProcessingStatus Source # 
Show TableProcessingStatus Source # 
Generic TableProcessingStatus Source # 
Hashable TableProcessingStatus Source # 
ToJSON TableProcessingStatus Source # 
FromJSON TableProcessingStatus Source # 
FromHttpApiData TableProcessingStatus Source # 
ToHttpApiData TableProcessingStatus Source # 
type Rep TableProcessingStatus Source # 
type Rep TableProcessingStatus = D1 (MetaData "TableProcessingStatus" "Network.Google.MapsEngine.Types.Sum" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) ((:+:) ((:+:) (C1 (MetaCons "TPSComplete" PrefixI False) U1) (C1 (MetaCons "TPSFailed" PrefixI False) U1)) ((:+:) (C1 (MetaCons "TPSNotReady" PrefixI False) U1) ((:+:) (C1 (MetaCons "TPSProcessing" PrefixI False) U1) (C1 (MetaCons "TPSReady" PrefixI False) U1))))

LineStyle

data LineStyle Source #

Style for lines.

See: lineStyle smart constructor.

Instances

Eq LineStyle Source # 
Data LineStyle Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LineStyle -> c LineStyle #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LineStyle #

toConstr :: LineStyle -> Constr #

dataTypeOf :: LineStyle -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LineStyle) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LineStyle) #

gmapT :: (forall b. Data b => b -> b) -> LineStyle -> LineStyle #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LineStyle -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LineStyle -> r #

gmapQ :: (forall d. Data d => d -> u) -> LineStyle -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LineStyle -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LineStyle -> m LineStyle #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LineStyle -> m LineStyle #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LineStyle -> m LineStyle #

Show LineStyle Source # 
Generic LineStyle Source # 

Associated Types

type Rep LineStyle :: * -> * #

ToJSON LineStyle Source # 
FromJSON LineStyle Source # 
type Rep LineStyle Source # 
type Rep LineStyle = D1 (MetaData "LineStyle" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "LineStyle'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_lsStroke") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LineStyleStroke))) (S1 (MetaSel (Just Symbol "_lsBOrder") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BOrder)))) ((:*:) (S1 (MetaSel (Just Symbol "_lsDash") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Textual Double]))) (S1 (MetaSel (Just Symbol "_lsLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LabelStyle))))))

lineStyle :: LineStyle Source #

Creates a value of LineStyle with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired:

lsBOrder :: Lens' LineStyle (Maybe BOrder) Source #

Border of the line. 0 < border.width <= 5.

lsDash :: Lens' LineStyle [Double] Source #

Dash defines the pattern of the line, the values are pixel lengths of alternating dash and gap. If dash is not provided, then it means a solid line. Dash can contain up to 10 values and must contain even number of values.

lsLabel :: Lens' LineStyle (Maybe LabelStyle) Source #

Label style for the line.

PublishedLayersListResponse

data PublishedLayersListResponse Source #

The response returned by a call to layers.List.published.

See: publishedLayersListResponse smart constructor.

Instances

Eq PublishedLayersListResponse Source # 
Data PublishedLayersListResponse Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> PublishedLayersListResponse -> c PublishedLayersListResponse #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c PublishedLayersListResponse #

toConstr :: PublishedLayersListResponse -> Constr #

dataTypeOf :: PublishedLayersListResponse -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c PublishedLayersListResponse) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c PublishedLayersListResponse) #

gmapT :: (forall b. Data b => b -> b) -> PublishedLayersListResponse -> PublishedLayersListResponse #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> PublishedLayersListResponse -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> PublishedLayersListResponse -> r #

gmapQ :: (forall d. Data d => d -> u) -> PublishedLayersListResponse -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> PublishedLayersListResponse -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> PublishedLayersListResponse -> m PublishedLayersListResponse #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> PublishedLayersListResponse -> m PublishedLayersListResponse #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> PublishedLayersListResponse -> m PublishedLayersListResponse #

Show PublishedLayersListResponse Source # 
Generic PublishedLayersListResponse Source # 
ToJSON PublishedLayersListResponse Source # 
FromJSON PublishedLayersListResponse Source # 
type Rep PublishedLayersListResponse Source # 
type Rep PublishedLayersListResponse = D1 (MetaData "PublishedLayersListResponse" "Network.Google.MapsEngine.Types.Product" "gogol-maps-engine-0.3.0-8urOfAmB6laBICTI61kKED" False) (C1 (MetaCons "PublishedLayersListResponse'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pllrNextPageToken") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Bytes))) (S1 (MetaSel (Just Symbol "_pllrLayers") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [PublishedLayer])))))

publishedLayersListResponse :: PublishedLayersListResponse Source #

Creates a value of PublishedLayersListResponse with the minimum fields required to make a request.

Use one of the following lenses to modify other fields as desired: