gogol-vision-0.1.1: Google Cloud Vision 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.Vision.Types

Contents

Description

 

Synopsis

Service Configuration

visionService :: ServiceConfig Source #

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

OAuth Scopes

cloudPlatformScope :: Proxy '["https://www.googleapis.com/auth/cloud-platform"] Source #

View and manage your data across Google Cloud Platform services

LatLng

data LatLng Source #

An object representing a latitude/longitude pair. This is expressed as a pair of doubles representing degrees latitude and degrees longitude. Unless specified otherwise, this must conform to the WGS84 standard. Values must be within normalized ranges. Example of normalization code in Python: def NormalizeLongitude(longitude): """Wraps decimal degrees longitude to [-180.0, 180.0].""" q, r = divmod(longitude, 360.0) if r > 180.0 or (r == 180.0 and q <= -1.0): return r - 360.0 return r def NormalizeLatLng(latitude, longitude): """Wraps decimal degrees latitude and longitude to [-90.0, 90.0] and [-180.0, 180.0], respectively.""" r = latitude % 360.0 if r <= 90.0: return r, NormalizeLongitude(longitude) elif r >= 270.0: return r - 360, NormalizeLongitude(longitude) else: return 180 - r, NormalizeLongitude(longitude + 180.0) assert 180.0 == NormalizeLongitude(180.0) assert -180.0 == NormalizeLongitude(-180.0) assert -179.0 == NormalizeLongitude(181.0) assert (0.0, 0.0) == NormalizeLatLng(360.0, 0.0) assert (0.0, 0.0) == NormalizeLatLng(-360.0, 0.0) assert (85.0, 180.0) == NormalizeLatLng(95.0, 0.0) assert (-85.0, -170.0) == NormalizeLatLng(-95.0, 10.0) assert (90.0, 10.0) == NormalizeLatLng(90.0, 10.0) assert (-90.0, -10.0) == NormalizeLatLng(-90.0, -10.0) assert (0.0, -170.0) == NormalizeLatLng(-180.0, 10.0) assert (0.0, -170.0) == NormalizeLatLng(180.0, 10.0) assert (-90.0, 10.0) == NormalizeLatLng(270.0, 10.0) assert (90.0, 10.0) == NormalizeLatLng(-270.0, 10.0)

See: latLng smart constructor.

Instances

Eq LatLng Source # 

Methods

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

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

Data LatLng Source # 

Methods

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

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

toConstr :: LatLng -> Constr #

dataTypeOf :: LatLng -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LatLng Source # 
Generic LatLng Source # 

Associated Types

type Rep LatLng :: * -> * #

Methods

from :: LatLng -> Rep LatLng x #

to :: Rep LatLng x -> LatLng #

ToJSON LatLng Source # 
FromJSON LatLng Source # 
type Rep LatLng Source # 
type Rep LatLng = D1 (MetaData "LatLng" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "LatLng'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_llLatitude") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_llLongitude") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))))

latLng :: LatLng Source #

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

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

llLatitude :: Lens' LatLng (Maybe Double) Source #

The latitude in degrees. It must be in the range [-90.0, +90.0].

llLongitude :: Lens' LatLng (Maybe Double) Source #

The longitude in degrees. It must be in the range [-180.0, +180.0].

FaceAnnotationUnderExposedLikelihood

data FaceAnnotationUnderExposedLikelihood Source #

Under-exposed likelihood.

Constructors

Unknown

UNKNOWN Unknown likelihood.

VeryUnlikely

VERY_UNLIKELY The image very unlikely belongs to the vertical specified.

Unlikely

UNLIKELY The image unlikely belongs to the vertical specified.

Possible

POSSIBLE The image possibly belongs to the vertical specified.

Likely

LIKELY The image likely belongs to the vertical specified.

VeryLikely

VERY_LIKELY The image very likely belongs to the vertical specified.

Instances

Enum FaceAnnotationUnderExposedLikelihood Source # 
Eq FaceAnnotationUnderExposedLikelihood Source # 
Data FaceAnnotationUnderExposedLikelihood Source # 

Methods

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

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

toConstr :: FaceAnnotationUnderExposedLikelihood -> Constr #

dataTypeOf :: FaceAnnotationUnderExposedLikelihood -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FaceAnnotationUnderExposedLikelihood Source # 
Read FaceAnnotationUnderExposedLikelihood Source # 
Show FaceAnnotationUnderExposedLikelihood Source # 
Generic FaceAnnotationUnderExposedLikelihood Source # 
Hashable FaceAnnotationUnderExposedLikelihood Source # 
ToJSON FaceAnnotationUnderExposedLikelihood Source # 
FromJSON FaceAnnotationUnderExposedLikelihood Source # 
FromHttpApiData FaceAnnotationUnderExposedLikelihood Source # 
ToHttpApiData FaceAnnotationUnderExposedLikelihood Source # 
type Rep FaceAnnotationUnderExposedLikelihood Source # 
type Rep FaceAnnotationUnderExposedLikelihood = D1 (MetaData "FaceAnnotationUnderExposedLikelihood" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) (C1 (MetaCons "Unknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "VeryUnlikely" PrefixI False) U1) (C1 (MetaCons "Unlikely" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Possible" PrefixI False) U1) ((:+:) (C1 (MetaCons "Likely" PrefixI False) U1) (C1 (MetaCons "VeryLikely" PrefixI False) U1))))

Feature

data Feature Source #

The Feature indicates what type of image detection task to perform. Users describe the type of Google Cloud Vision API tasks to perform over images by using Features. Features encode the Cloud Vision API vertical to operate on and the number of top-scoring results to return.

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.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "Feature'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_fType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FeatureType))) (S1 (MetaSel (Just Symbol "_fMaxResults") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

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:

fType :: Lens' Feature (Maybe FeatureType) Source #

The feature type.

fMaxResults :: Lens' Feature (Maybe Int32) Source #

Maximum number of results of this type.

Status

data Status Source #

The `Status` type defines a logical error model that is suitable for different programming environments, including REST APIs and RPC APIs. It is used by gRPC. The error model is designed to be: - Simple to use and understand for most users - Flexible enough to meet unexpected needs # Overview The `Status` message contains three pieces of data: error code, error message, and error details. The error code should be an enum value of google.rpc.Code, but it may accept additional error codes if needed. The error message should be a developer-facing English message that helps developers *understand* and *resolve* the error. If a localized user-facing error message is needed, put the localized message in the error details or localize it in the client. The optional error details may contain arbitrary information about the error. There is a predefined set of error detail types in the package `google.rpc` which can be used for common error conditions. # Language mapping The `Status` message is the logical representation of the error model, but it is not necessarily the actual wire format. When the `Status` message is exposed in different client libraries and different wire protocols, it can be mapped differently. For example, it will likely be mapped to some exceptions in Java, but more likely mapped to some error codes in C. # Other uses The error model and the `Status` message can be used in a variety of environments, either with or without APIs, to provide a consistent developer experience across different environments. Example uses of this error model include: - Partial errors. If a service needs to return partial errors to the client, it may embed the `Status` in the normal response to indicate the partial errors. - Workflow errors. A typical workflow has multiple steps. Each step may have a `Status` message for error reporting purpose. - Batch operations. If a client uses batch request and batch response, the `Status` message should be used directly inside batch response, one for each error sub-response. - Asynchronous operations. If an API call embeds asynchronous operation results in its response, the status of those operations should be represented directly using the `Status` message. - Logging. If some API errors are stored in logs, the message `Status` could be used directly after any stripping needed for security/privacy reasons.

See: status smart constructor.

Instances

Eq Status Source # 

Methods

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

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

Data Status Source # 

Methods

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

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

toConstr :: Status -> Constr #

dataTypeOf :: Status -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Status Source # 
Generic Status Source # 

Associated Types

type Rep Status :: * -> * #

Methods

from :: Status -> Rep Status x #

to :: Rep Status x -> Status #

ToJSON Status Source # 
FromJSON Status Source # 
type Rep Status Source # 
type Rep Status = D1 (MetaData "Status" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "Status'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_sDetails") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [StatusDetailsItem]))) ((:*:) (S1 (MetaSel (Just Symbol "_sCode") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_sMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

status :: Status Source #

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

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

sDetails :: Lens' Status [StatusDetailsItem] Source #

A list of messages that carry the error details. There will be a common set of message types for APIs to use.

sCode :: Lens' Status (Maybe Int32) Source #

The status code, which should be an enum value of google.rpc.Code.

sMessage :: Lens' Status (Maybe Text) Source #

A developer-facing error message, which should be in English. Any user-facing error message should be localized and sent in the google.rpc.Status.details field, or localized by the client.

Property

data Property Source #

Arbitrary name/value pair.

See: property smart constructor.

Instances

Eq Property Source # 
Data Property Source # 

Methods

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

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

toConstr :: Property -> Constr #

dataTypeOf :: Property -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Property Source # 
Generic Property Source # 

Associated Types

type Rep Property :: * -> * #

Methods

from :: Property -> Rep Property x #

to :: Rep Property x -> Property #

ToJSON Property Source # 
FromJSON Property Source # 
type Rep Property Source # 
type Rep Property = D1 (MetaData "Property" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "Property'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pValue") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

property :: Property Source #

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

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

pValue :: Lens' Property (Maybe Text) Source #

Value of the property.

pName :: Lens' Property (Maybe Text) Source #

Name of the property.

Image

data Image Source #

Client image to perform Google Cloud Vision API tasks over.

See: image smart constructor.

Instances

Eq Image Source # 

Methods

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

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

Data Image Source # 

Methods

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

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

toConstr :: Image -> Constr #

dataTypeOf :: Image -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Image Source # 

Methods

showsPrec :: Int -> Image -> ShowS #

show :: Image -> String #

showList :: [Image] -> ShowS #

Generic Image Source # 

Associated Types

type Rep Image :: * -> * #

Methods

from :: Image -> Rep Image x #

to :: Rep Image x -> Image #

ToJSON Image Source # 
FromJSON Image Source # 
type Rep Image Source # 
type Rep Image = D1 (MetaData "Image" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "Image'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_iContent") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Base64))) (S1 (MetaSel (Just Symbol "_iSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ImageSource)))))

image :: Image Source #

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

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

iContent :: Lens' Image (Maybe ByteString) Source #

Image content, represented as a stream of bytes. Note: as with all `bytes` fields, protobuffers use a pure binary representation, whereas JSON representations use base64.

iSource :: Lens' Image (Maybe ImageSource) Source #

Google Cloud Storage image location. If both 'content' and 'source' are filled for an image, 'content' takes precedence and it will be used for performing the image annotation request.

Landmark

data Landmark Source #

A face-specific landmark (for example, a face feature). Landmark positions may fall outside the bounds of the image when the face is near one or more edges of the image. Therefore it is NOT guaranteed that 0 <= x < width or 0 <= y < height.

See: landmark smart constructor.

Instances

Eq Landmark Source # 
Data Landmark Source # 

Methods

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

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

toConstr :: Landmark -> Constr #

dataTypeOf :: Landmark -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Landmark Source # 
Generic Landmark Source # 

Associated Types

type Rep Landmark :: * -> * #

Methods

from :: Landmark -> Rep Landmark x #

to :: Rep Landmark x -> Landmark #

ToJSON Landmark Source # 
FromJSON Landmark Source # 
type Rep Landmark Source # 
type Rep Landmark = D1 (MetaData "Landmark" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "Landmark'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_lType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LandmarkType))) (S1 (MetaSel (Just Symbol "_lPosition") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Position)))))

landmark :: Landmark Source #

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

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

lType :: Lens' Landmark (Maybe LandmarkType) Source #

Face landmark type.

lPosition :: Lens' Landmark (Maybe Position) Source #

Face landmark position.

Color

data Color Source #

Represents a color in the RGBA color space. This representation is designed for simplicity of conversion to/from color representations in various languages over compactness; for example, the fields of this representation can be trivially provided to the constructor of "java.awt.Color" in Java; it can also be trivially provided to UIColor's "+colorWithRed:green:blue:alpha" method in iOS; and, with just a little work, it can be easily formatted into a CSS "rgba()" string in JavaScript, as well. Here are some examples: Example (Java): import com.google.type.Color; // ... public static java.awt.Color fromProto(Color protocolor) { float alpha = protocolor.hasAlpha() ? protocolor.getAlpha().getValue() : 1.0; return new java.awt.Color( protocolor.getRed(), protocolor.getGreen(), protocolor.getBlue(), alpha); } public static Color toProto(java.awt.Color color) { float red = (float) color.getRed(); float green = (float) color.getGreen(); float blue = (float) color.getBlue(); float denominator = 255.0; Color.Builder resultBuilder = Color .newBuilder() .setRed(red / denominator) .setGreen(green / denominator) .setBlue(blue / denominator); int alpha = color.getAlpha(); if (alpha != 255) { result.setAlpha( FloatValue .newBuilder() .setValue(((float) alpha) / denominator) .build()); } return resultBuilder.build(); } // ... Example (iOS / Obj-C): // ... static UIColor* fromProto(Color* protocolor) { float red = [protocolor red]; float green = [protocolor green]; float blue = [protocolor blue]; FloatValue* alpha_wrapper = [protocolor alpha]; float alpha = 1.0; if (alpha_wrapper != nil) { alpha = [alpha_wrapper value]; } return [UIColor colorWithRed:red green:green blue:blue alpha:alpha]; } static Color* toProto(UIColor* color) { CGFloat red, green, blue, alpha; if (![color getRed:&red green:&green blue:&blue alpha:&alpha]) { return nil; } Color* result = [Color alloc] init]; [result setRed:red]; [result setGreen:green]; [result setBlue:blue]; if (alpha <= 0.9999) { [result setAlpha:floatWrapperWithValue(alpha)]; } [result autorelease]; return result; } // ... Example (JavaScript): // ... var protoToCssColor = function(rgb_color) { var redFrac = rgb_color.red || 0.0; var greenFrac = rgb_color.green || 0.0; var blueFrac = rgb_color.blue || 0.0; var red = Math.floor(redFrac * 255); var green = Math.floor(greenFrac * 255); var blue = Math.floor(blueFrac * 255); if (!('alpha' in rgb_color)) { return rgbToCssColor_(red, green, blue); } var alphaFrac = rgb_color.alpha.value || 0.0; var rgbParams = [red, green, blue].join(','); return ['rgba(', rgbParams, ',', alphaFrac, ')'].join(''); }; var rgbToCssColor_ = function(red, green, blue) { var rgbNumber = new Number((red << 16) | (green << 8) | blue); var hexString = rgbNumber.toString(16); var missingZeros = 6 - hexString.length; var resultBuilder = ['#']; for (var i = 0; i < missingZeros; i++) { resultBuilder.push('0'); } resultBuilder.push(hexString); return resultBuilder.join(''); }; // ...

See: color smart constructor.

Instances

Eq Color Source # 

Methods

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

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

Data Color Source # 

Methods

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

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

toConstr :: Color -> Constr #

dataTypeOf :: Color -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Color Source # 

Methods

showsPrec :: Int -> Color -> ShowS #

show :: Color -> String #

showList :: [Color] -> ShowS #

Generic Color Source # 

Associated Types

type Rep Color :: * -> * #

Methods

from :: Color -> Rep Color x #

to :: Rep Color x -> Color #

ToJSON Color Source # 
FromJSON Color Source # 
type Rep Color Source # 

color :: Color Source #

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

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

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

The amount of red in the color as a value in the interval [0, 1].

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

The fraction of this color that should be applied to the pixel. That is, the final pixel color is defined by the equation: pixel color = alpha * (this color) + (1.0 - alpha) * (background color) This means that a value of 1.0 corresponds to a solid color, whereas a value of 0.0 corresponds to a completely transparent color. This uses a wrapper message rather than a simple float scalar so that it is possible to distinguish between a default value and the value being unset. If omitted, this color object is to be rendered as a solid color (as if the alpha value had been explicitly given with a value of 1.0).

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

The amount of green in the color as a value in the interval [0, 1].

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

The amount of blue in the color as a value in the interval [0, 1].

FaceAnnotationHeadwearLikelihood

data FaceAnnotationHeadwearLikelihood Source #

Headwear likelihood.

Constructors

FAHLUnknown

UNKNOWN Unknown likelihood.

FAHLVeryUnlikely

VERY_UNLIKELY The image very unlikely belongs to the vertical specified.

FAHLUnlikely

UNLIKELY The image unlikely belongs to the vertical specified.

FAHLPossible

POSSIBLE The image possibly belongs to the vertical specified.

FAHLLikely

LIKELY The image likely belongs to the vertical specified.

FAHLVeryLikely

VERY_LIKELY The image very likely belongs to the vertical specified.

Instances

Enum FaceAnnotationHeadwearLikelihood Source # 
Eq FaceAnnotationHeadwearLikelihood Source # 
Data FaceAnnotationHeadwearLikelihood Source # 

Methods

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

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

toConstr :: FaceAnnotationHeadwearLikelihood -> Constr #

dataTypeOf :: FaceAnnotationHeadwearLikelihood -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FaceAnnotationHeadwearLikelihood Source # 
Read FaceAnnotationHeadwearLikelihood Source # 
Show FaceAnnotationHeadwearLikelihood Source # 
Generic FaceAnnotationHeadwearLikelihood Source # 
Hashable FaceAnnotationHeadwearLikelihood Source # 
ToJSON FaceAnnotationHeadwearLikelihood Source # 
FromJSON FaceAnnotationHeadwearLikelihood Source # 
FromHttpApiData FaceAnnotationHeadwearLikelihood Source # 
ToHttpApiData FaceAnnotationHeadwearLikelihood Source # 
type Rep FaceAnnotationHeadwearLikelihood Source # 
type Rep FaceAnnotationHeadwearLikelihood = D1 (MetaData "FaceAnnotationHeadwearLikelihood" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) (C1 (MetaCons "FAHLUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "FAHLVeryUnlikely" PrefixI False) U1) (C1 (MetaCons "FAHLUnlikely" PrefixI False) U1))) ((:+:) (C1 (MetaCons "FAHLPossible" PrefixI False) U1) ((:+:) (C1 (MetaCons "FAHLLikely" PrefixI False) U1) (C1 (MetaCons "FAHLVeryLikely" PrefixI False) U1))))

BoundingPoly

data BoundingPoly Source #

A bounding polygon for the detected image annotation.

See: boundingPoly smart constructor.

Instances

Eq BoundingPoly Source # 
Data BoundingPoly Source # 

Methods

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

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

toConstr :: BoundingPoly -> Constr #

dataTypeOf :: BoundingPoly -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BoundingPoly Source # 
Generic BoundingPoly Source # 

Associated Types

type Rep BoundingPoly :: * -> * #

ToJSON BoundingPoly Source # 
FromJSON BoundingPoly Source # 
type Rep BoundingPoly Source # 
type Rep BoundingPoly = D1 (MetaData "BoundingPoly" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" True) (C1 (MetaCons "BoundingPoly'" PrefixI True) (S1 (MetaSel (Just Symbol "_bpVertices") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [Vertex]))))

boundingPoly :: BoundingPoly Source #

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

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

bpVertices :: Lens' BoundingPoly [Vertex] Source #

The bounding polygon vertices.

SafeSearchAnnotationAdult

data SafeSearchAnnotationAdult Source #

Represents the adult contents likelihood for the image.

Constructors

SSAAUnknown

UNKNOWN Unknown likelihood.

SSAAVeryUnlikely

VERY_UNLIKELY The image very unlikely belongs to the vertical specified.

SSAAUnlikely

UNLIKELY The image unlikely belongs to the vertical specified.

SSAAPossible

POSSIBLE The image possibly belongs to the vertical specified.

SSAALikely

LIKELY The image likely belongs to the vertical specified.

SSAAVeryLikely

VERY_LIKELY The image very likely belongs to the vertical specified.

Instances

Enum SafeSearchAnnotationAdult Source # 
Eq SafeSearchAnnotationAdult Source # 
Data SafeSearchAnnotationAdult Source # 

Methods

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

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

toConstr :: SafeSearchAnnotationAdult -> Constr #

dataTypeOf :: SafeSearchAnnotationAdult -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SafeSearchAnnotationAdult Source # 
Read SafeSearchAnnotationAdult Source # 
Show SafeSearchAnnotationAdult Source # 
Generic SafeSearchAnnotationAdult Source # 
Hashable SafeSearchAnnotationAdult Source # 
ToJSON SafeSearchAnnotationAdult Source # 
FromJSON SafeSearchAnnotationAdult Source # 
FromHttpApiData SafeSearchAnnotationAdult Source # 
ToHttpApiData SafeSearchAnnotationAdult Source # 
type Rep SafeSearchAnnotationAdult Source # 
type Rep SafeSearchAnnotationAdult = D1 (MetaData "SafeSearchAnnotationAdult" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) (C1 (MetaCons "SSAAUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "SSAAVeryUnlikely" PrefixI False) U1) (C1 (MetaCons "SSAAUnlikely" PrefixI False) U1))) ((:+:) (C1 (MetaCons "SSAAPossible" PrefixI False) U1) ((:+:) (C1 (MetaCons "SSAALikely" PrefixI False) U1) (C1 (MetaCons "SSAAVeryLikely" PrefixI False) U1))))

Vertex

data Vertex Source #

A vertex represents a 2D point in the image. NOTE: the vertex coordinates are in the same scale as the original image.

See: vertex smart constructor.

Instances

Eq Vertex Source # 

Methods

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

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

Data Vertex Source # 

Methods

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

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

toConstr :: Vertex -> Constr #

dataTypeOf :: Vertex -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Vertex Source # 
Generic Vertex Source # 

Associated Types

type Rep Vertex :: * -> * #

Methods

from :: Vertex -> Rep Vertex x #

to :: Rep Vertex x -> Vertex #

ToJSON Vertex Source # 
FromJSON Vertex Source # 
type Rep Vertex Source # 
type Rep Vertex = D1 (MetaData "Vertex" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "Vertex'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_vX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_vY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

vertex :: Vertex Source #

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

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

vX :: Lens' Vertex (Maybe Int32) Source #

X coordinate.

vY :: Lens' Vertex (Maybe Int32) Source #

Y coordinate.

FaceAnnotationAngerLikelihood

data FaceAnnotationAngerLikelihood Source #

Anger likelihood.

Constructors

FAALUnknown

UNKNOWN Unknown likelihood.

FAALVeryUnlikely

VERY_UNLIKELY The image very unlikely belongs to the vertical specified.

FAALUnlikely

UNLIKELY The image unlikely belongs to the vertical specified.

FAALPossible

POSSIBLE The image possibly belongs to the vertical specified.

FAALLikely

LIKELY The image likely belongs to the vertical specified.

FAALVeryLikely

VERY_LIKELY The image very likely belongs to the vertical specified.

Instances

Enum FaceAnnotationAngerLikelihood Source # 
Eq FaceAnnotationAngerLikelihood Source # 
Data FaceAnnotationAngerLikelihood Source # 

Methods

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

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

toConstr :: FaceAnnotationAngerLikelihood -> Constr #

dataTypeOf :: FaceAnnotationAngerLikelihood -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FaceAnnotationAngerLikelihood Source # 
Read FaceAnnotationAngerLikelihood Source # 
Show FaceAnnotationAngerLikelihood Source # 
Generic FaceAnnotationAngerLikelihood Source # 
Hashable FaceAnnotationAngerLikelihood Source # 
ToJSON FaceAnnotationAngerLikelihood Source # 
FromJSON FaceAnnotationAngerLikelihood Source # 
FromHttpApiData FaceAnnotationAngerLikelihood Source # 
ToHttpApiData FaceAnnotationAngerLikelihood Source # 
type Rep FaceAnnotationAngerLikelihood Source # 
type Rep FaceAnnotationAngerLikelihood = D1 (MetaData "FaceAnnotationAngerLikelihood" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) (C1 (MetaCons "FAALUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "FAALVeryUnlikely" PrefixI False) U1) (C1 (MetaCons "FAALUnlikely" PrefixI False) U1))) ((:+:) (C1 (MetaCons "FAALPossible" PrefixI False) U1) ((:+:) (C1 (MetaCons "FAALLikely" PrefixI False) U1) (C1 (MetaCons "FAALVeryLikely" PrefixI False) U1))))

LocationInfo

data LocationInfo Source #

Detected entity location information.

See: locationInfo smart constructor.

Instances

Eq LocationInfo Source # 
Data LocationInfo Source # 

Methods

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

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

toConstr :: LocationInfo -> Constr #

dataTypeOf :: LocationInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LocationInfo Source # 
Generic LocationInfo Source # 

Associated Types

type Rep LocationInfo :: * -> * #

ToJSON LocationInfo Source # 
FromJSON LocationInfo Source # 
type Rep LocationInfo Source # 
type Rep LocationInfo = D1 (MetaData "LocationInfo" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" True) (C1 (MetaCons "LocationInfo'" PrefixI True) (S1 (MetaSel (Just Symbol "_liLatLng") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe LatLng))))

locationInfo :: LocationInfo Source #

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

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

liLatLng :: Lens' LocationInfo (Maybe LatLng) Source #

Lat - long location coordinates.

SafeSearchAnnotationMedical

data SafeSearchAnnotationMedical Source #

Likelihood this is a medical image.

Constructors

SSAMUnknown

UNKNOWN Unknown likelihood.

SSAMVeryUnlikely

VERY_UNLIKELY The image very unlikely belongs to the vertical specified.

SSAMUnlikely

UNLIKELY The image unlikely belongs to the vertical specified.

SSAMPossible

POSSIBLE The image possibly belongs to the vertical specified.

SSAMLikely

LIKELY The image likely belongs to the vertical specified.

SSAMVeryLikely

VERY_LIKELY The image very likely belongs to the vertical specified.

Instances

Enum SafeSearchAnnotationMedical Source # 
Eq SafeSearchAnnotationMedical Source # 
Data SafeSearchAnnotationMedical Source # 

Methods

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

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

toConstr :: SafeSearchAnnotationMedical -> Constr #

dataTypeOf :: SafeSearchAnnotationMedical -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SafeSearchAnnotationMedical Source # 
Read SafeSearchAnnotationMedical Source # 
Show SafeSearchAnnotationMedical Source # 
Generic SafeSearchAnnotationMedical Source # 
Hashable SafeSearchAnnotationMedical Source # 
ToJSON SafeSearchAnnotationMedical Source # 
FromJSON SafeSearchAnnotationMedical Source # 
FromHttpApiData SafeSearchAnnotationMedical Source # 
ToHttpApiData SafeSearchAnnotationMedical Source # 
type Rep SafeSearchAnnotationMedical Source # 
type Rep SafeSearchAnnotationMedical = D1 (MetaData "SafeSearchAnnotationMedical" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) (C1 (MetaCons "SSAMUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "SSAMVeryUnlikely" PrefixI False) U1) (C1 (MetaCons "SSAMUnlikely" PrefixI False) U1))) ((:+:) (C1 (MetaCons "SSAMPossible" PrefixI False) U1) ((:+:) (C1 (MetaCons "SSAMLikely" PrefixI False) U1) (C1 (MetaCons "SSAMVeryLikely" PrefixI False) U1))))

StatusDetailsItem

data StatusDetailsItem Source #

Instances

Eq StatusDetailsItem Source # 
Data StatusDetailsItem Source # 

Methods

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

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

toConstr :: StatusDetailsItem -> Constr #

dataTypeOf :: StatusDetailsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show StatusDetailsItem Source # 
Generic StatusDetailsItem Source # 
ToJSON StatusDetailsItem Source # 
FromJSON StatusDetailsItem Source # 
type Rep StatusDetailsItem Source # 
type Rep StatusDetailsItem = D1 (MetaData "StatusDetailsItem" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" True) (C1 (MetaCons "StatusDetailsItem'" PrefixI True) (S1 (MetaSel (Just Symbol "_sdiAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

statusDetailsItem Source #

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

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

sdiAddtional :: Lens' StatusDetailsItem (HashMap Text JSONValue) Source #

Properties of the object. Contains field 'type with type URL.

BatchAnnotateImagesRequest

data BatchAnnotateImagesRequest Source #

Multiple image annotation requests are batched into a single service call.

See: batchAnnotateImagesRequest smart constructor.

Instances

Eq BatchAnnotateImagesRequest Source # 
Data BatchAnnotateImagesRequest Source # 

Methods

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

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

toConstr :: BatchAnnotateImagesRequest -> Constr #

dataTypeOf :: BatchAnnotateImagesRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BatchAnnotateImagesRequest Source # 
Generic BatchAnnotateImagesRequest Source # 
ToJSON BatchAnnotateImagesRequest Source # 
FromJSON BatchAnnotateImagesRequest Source # 
type Rep BatchAnnotateImagesRequest Source # 
type Rep BatchAnnotateImagesRequest = D1 (MetaData "BatchAnnotateImagesRequest" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" True) (C1 (MetaCons "BatchAnnotateImagesRequest'" PrefixI True) (S1 (MetaSel (Just Symbol "_bairRequests") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [AnnotateImageRequest]))))

batchAnnotateImagesRequest :: BatchAnnotateImagesRequest Source #

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

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

bairRequests :: Lens' BatchAnnotateImagesRequest [AnnotateImageRequest] Source #

Individual image annotation requests for this batch.

ColorInfo

data ColorInfo Source #

Color information consists of RGB channels, score and fraction of image the color occupies in the image.

See: colorInfo smart constructor.

Instances

Eq ColorInfo Source # 
Data ColorInfo Source # 

Methods

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

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

toConstr :: ColorInfo -> Constr #

dataTypeOf :: ColorInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ColorInfo Source # 
Generic ColorInfo Source # 

Associated Types

type Rep ColorInfo :: * -> * #

ToJSON ColorInfo Source # 
FromJSON ColorInfo Source # 
type Rep ColorInfo Source # 
type Rep ColorInfo = D1 (MetaData "ColorInfo" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "ColorInfo'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ciColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Color))) ((:*:) (S1 (MetaSel (Just Symbol "_ciScore") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_ciPixelFraction") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))))))

colorInfo :: ColorInfo Source #

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

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

ciColor :: Lens' ColorInfo (Maybe Color) Source #

RGB components of the color.

ciScore :: Lens' ColorInfo (Maybe Double) Source #

Image-specific score for this color. Value in range [0, 1].

ciPixelFraction :: Lens' ColorInfo (Maybe Double) Source #

Stores the fraction of pixels the color occupies in the image. Value in range [0, 1].

FaceAnnotationBlurredLikelihood

data FaceAnnotationBlurredLikelihood Source #

Blurred likelihood.

Constructors

FABLUnknown

UNKNOWN Unknown likelihood.

FABLVeryUnlikely

VERY_UNLIKELY The image very unlikely belongs to the vertical specified.

FABLUnlikely

UNLIKELY The image unlikely belongs to the vertical specified.

FABLPossible

POSSIBLE The image possibly belongs to the vertical specified.

FABLLikely

LIKELY The image likely belongs to the vertical specified.

FABLVeryLikely

VERY_LIKELY The image very likely belongs to the vertical specified.

Instances

Enum FaceAnnotationBlurredLikelihood Source # 
Eq FaceAnnotationBlurredLikelihood Source # 
Data FaceAnnotationBlurredLikelihood Source # 

Methods

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

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

toConstr :: FaceAnnotationBlurredLikelihood -> Constr #

dataTypeOf :: FaceAnnotationBlurredLikelihood -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FaceAnnotationBlurredLikelihood Source # 
Read FaceAnnotationBlurredLikelihood Source # 
Show FaceAnnotationBlurredLikelihood Source # 
Generic FaceAnnotationBlurredLikelihood Source # 
Hashable FaceAnnotationBlurredLikelihood Source # 
ToJSON FaceAnnotationBlurredLikelihood Source # 
FromJSON FaceAnnotationBlurredLikelihood Source # 
FromHttpApiData FaceAnnotationBlurredLikelihood Source # 
ToHttpApiData FaceAnnotationBlurredLikelihood Source # 
type Rep FaceAnnotationBlurredLikelihood Source # 
type Rep FaceAnnotationBlurredLikelihood = D1 (MetaData "FaceAnnotationBlurredLikelihood" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) (C1 (MetaCons "FABLUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "FABLVeryUnlikely" PrefixI False) U1) (C1 (MetaCons "FABLUnlikely" PrefixI False) U1))) ((:+:) (C1 (MetaCons "FABLPossible" PrefixI False) U1) ((:+:) (C1 (MetaCons "FABLLikely" PrefixI False) U1) (C1 (MetaCons "FABLVeryLikely" PrefixI False) U1))))

AnnotateImageResponse

data AnnotateImageResponse Source #

Response to an image annotation request.

See: annotateImageResponse smart constructor.

Instances

Eq AnnotateImageResponse Source # 
Data AnnotateImageResponse Source # 

Methods

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

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

toConstr :: AnnotateImageResponse -> Constr #

dataTypeOf :: AnnotateImageResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

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

airLogoAnnotations :: Lens' AnnotateImageResponse [EntityAnnotation] Source #

If present, logo detection completed successfully.

airLabelAnnotations :: Lens' AnnotateImageResponse [EntityAnnotation] Source #

If present, label detection completed successfully.

airFaceAnnotations :: Lens' AnnotateImageResponse [FaceAnnotation] Source #

If present, face detection completed successfully.

airError :: Lens' AnnotateImageResponse (Maybe Status) Source #

If set, represents the error message for the operation. Note that filled-in mage annotations are guaranteed to be correct, even when error is non-empty.

airSafeSearchAnnotation :: Lens' AnnotateImageResponse (Maybe SafeSearchAnnotation) Source #

If present, safe-search annotation completed successfully.

airLandmarkAnnotations :: Lens' AnnotateImageResponse [EntityAnnotation] Source #

If present, landmark detection completed successfully.

airTextAnnotations :: Lens' AnnotateImageResponse [EntityAnnotation] Source #

If present, text (OCR) detection completed successfully.

airImagePropertiesAnnotation :: Lens' AnnotateImageResponse (Maybe ImageProperties) Source #

If present, image properties were extracted successfully.

ImageProperties

data ImageProperties Source #

Stores image properties (e.g. dominant colors).

See: imageProperties smart constructor.

Instances

Eq ImageProperties Source # 
Data ImageProperties Source # 

Methods

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

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

toConstr :: ImageProperties -> Constr #

dataTypeOf :: ImageProperties -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ImageProperties Source # 
Generic ImageProperties Source # 
ToJSON ImageProperties Source # 
FromJSON ImageProperties Source # 
type Rep ImageProperties Source # 
type Rep ImageProperties = D1 (MetaData "ImageProperties" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" True) (C1 (MetaCons "ImageProperties'" PrefixI True) (S1 (MetaSel (Just Symbol "_ipDominantColors") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe DominantColorsAnnotation))))

imageProperties :: ImageProperties Source #

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

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

ipDominantColors :: Lens' ImageProperties (Maybe DominantColorsAnnotation) Source #

If present, dominant colors completed successfully.

FaceAnnotation

data FaceAnnotation Source #

A face annotation object contains the results of face detection.

See: faceAnnotation smart constructor.

Instances

Eq FaceAnnotation Source # 
Data FaceAnnotation Source # 

Methods

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

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

toConstr :: FaceAnnotation -> Constr #

dataTypeOf :: FaceAnnotation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show FaceAnnotation Source # 
Generic FaceAnnotation Source # 

Associated Types

type Rep FaceAnnotation :: * -> * #

ToJSON FaceAnnotation Source # 
FromJSON FaceAnnotation Source # 
type Rep FaceAnnotation Source # 
type Rep FaceAnnotation = D1 (MetaData "FaceAnnotation" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "FaceAnnotation'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faTiltAngle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) ((:*:) (S1 (MetaSel (Just Symbol "_faBlurredLikelihood") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FaceAnnotationBlurredLikelihood))) (S1 (MetaSel (Just Symbol "_faBoundingPoly") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BoundingPoly))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faSurpriseLikelihood") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FaceAnnotationSurpriseLikelihood))) (S1 (MetaSel (Just Symbol "_faLandmarkingConfidence") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))) ((:*:) (S1 (MetaSel (Just Symbol "_faPanAngle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_faRollAngle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faUnderExposedLikelihood") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FaceAnnotationUnderExposedLikelihood))) (S1 (MetaSel (Just Symbol "_faFdBoundingPoly") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe BoundingPoly)))) ((:*:) (S1 (MetaSel (Just Symbol "_faAngerLikelihood") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FaceAnnotationAngerLikelihood))) (S1 (MetaSel (Just Symbol "_faDetectionConfidence") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_faHeadwearLikelihood") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FaceAnnotationHeadwearLikelihood))) (S1 (MetaSel (Just Symbol "_faSorrowLikelihood") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FaceAnnotationSorrowLikelihood)))) ((:*:) (S1 (MetaSel (Just Symbol "_faJoyLikelihood") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe FaceAnnotationJoyLikelihood))) (S1 (MetaSel (Just Symbol "_faLandmarks") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Landmark]))))))))

faTiltAngle :: Lens' FaceAnnotation (Maybe Double) Source #

Pitch angle. Indicates the upwards/downwards angle that the face is pointing relative to the image's horizontal plane. Range [-180,180].

faBoundingPoly :: Lens' FaceAnnotation (Maybe BoundingPoly) Source #

The bounding polygon around the face. The coordinates of the bounding box are in the original image's scale, as returned in ImageParams. The bounding box is computed to "frame" the face in accordance with human expectations. It is based on the landmarker results. Note that one or more x and/or y coordinates may not be generated in the BoundingPoly (the polygon will be unbounded) if only a partial face appears in the image to be annotated.

faLandmarkingConfidence :: Lens' FaceAnnotation (Maybe Double) Source #

Face landmarking confidence. Range [0, 1].

faPanAngle :: Lens' FaceAnnotation (Maybe Double) Source #

Yaw angle. Indicates the leftward/rightward angle that the face is pointing, relative to the vertical plane perpendicular to the image. Range [-180,180].

faRollAngle :: Lens' FaceAnnotation (Maybe Double) Source #

Roll angle. Indicates the amount of clockwise/anti-clockwise rotation of the face relative to the image vertical, about the axis perpendicular to the face. Range [-180,180].

faFdBoundingPoly :: Lens' FaceAnnotation (Maybe BoundingPoly) Source #

This bounding polygon is tighter than the previous boundingPoly, and encloses only the skin part of the face. Typically, it is used to eliminate the face from any image analysis that detects the "amount of skin" visible in an image. It is not based on the landmarker results, only on the initial face detection, hence the fd (face detection) prefix.

faDetectionConfidence :: Lens' FaceAnnotation (Maybe Double) Source #

Detection confidence. Range [0, 1].

faLandmarks :: Lens' FaceAnnotation [Landmark] Source #

Detected face landmarks.

SafeSearchAnnotationViolence

data SafeSearchAnnotationViolence Source #

Violence likelihood.

Constructors

SSAVUnknown

UNKNOWN Unknown likelihood.

SSAVVeryUnlikely

VERY_UNLIKELY The image very unlikely belongs to the vertical specified.

SSAVUnlikely

UNLIKELY The image unlikely belongs to the vertical specified.

SSAVPossible

POSSIBLE The image possibly belongs to the vertical specified.

SSAVLikely

LIKELY The image likely belongs to the vertical specified.

SSAVVeryLikely

VERY_LIKELY The image very likely belongs to the vertical specified.

Instances

Enum SafeSearchAnnotationViolence Source # 
Eq SafeSearchAnnotationViolence Source # 
Data SafeSearchAnnotationViolence Source # 

Methods

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

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

toConstr :: SafeSearchAnnotationViolence -> Constr #

dataTypeOf :: SafeSearchAnnotationViolence -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SafeSearchAnnotationViolence Source # 
Read SafeSearchAnnotationViolence Source # 
Show SafeSearchAnnotationViolence Source # 
Generic SafeSearchAnnotationViolence Source # 
Hashable SafeSearchAnnotationViolence Source # 
ToJSON SafeSearchAnnotationViolence Source # 
FromJSON SafeSearchAnnotationViolence Source # 
FromHttpApiData SafeSearchAnnotationViolence Source # 
ToHttpApiData SafeSearchAnnotationViolence Source # 
type Rep SafeSearchAnnotationViolence Source # 
type Rep SafeSearchAnnotationViolence = D1 (MetaData "SafeSearchAnnotationViolence" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) (C1 (MetaCons "SSAVUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "SSAVVeryUnlikely" PrefixI False) U1) (C1 (MetaCons "SSAVUnlikely" PrefixI False) U1))) ((:+:) (C1 (MetaCons "SSAVPossible" PrefixI False) U1) ((:+:) (C1 (MetaCons "SSAVLikely" PrefixI False) U1) (C1 (MetaCons "SSAVVeryLikely" PrefixI False) U1))))

EntityAnnotation

data EntityAnnotation Source #

Set of detected entity features.

See: entityAnnotation smart constructor.

Instances

Eq EntityAnnotation Source # 
Data EntityAnnotation Source # 

Methods

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

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

toConstr :: EntityAnnotation -> Constr #

dataTypeOf :: EntityAnnotation -> DataType #

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

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

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

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

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

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

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

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

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

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

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

entityAnnotation :: EntityAnnotation Source #

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

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

eaScore :: Lens' EntityAnnotation (Maybe Double) Source #

Overall score of the result. Range [0, 1].

eaTopicality :: Lens' EntityAnnotation (Maybe Double) Source #

The relevancy of the ICA (Image Content Annotation) label to the image. For example, the relevancy of 'tower' to an image containing 'Eiffel Tower' is likely higher than an image containing a distant towering building, though the confidence that there is a tower may be the same. Range [0, 1].

eaLocale :: Lens' EntityAnnotation (Maybe Text) Source #

The language code for the locale in which the entity textual description (next field) is expressed.

eaBoundingPoly :: Lens' EntityAnnotation (Maybe BoundingPoly) Source #

Image region to which this entity belongs. Not filled currently for `LABEL_DETECTION` features. For `TEXT_DETECTION` (OCR), `boundingPoly`s are produced for the entire text detected in an image region, followed by `boundingPoly`s for each word within the detected text.

eaConfidence :: Lens' EntityAnnotation (Maybe Double) Source #

The accuracy of the entity detection in an image. For example, for an image containing 'Eiffel Tower,' this field represents the confidence that there is a tower in the query image. Range [0, 1].

eaMid :: Lens' EntityAnnotation (Maybe Text) Source #

Opaque entity ID. Some IDs might be available in Knowledge Graph(KG). For more details on KG please see: https://developers.google.com/knowledge-graph/

eaLocations :: Lens' EntityAnnotation [LocationInfo] Source #

The location information for the detected entity. Multiple LocationInfo elements can be present since one location may indicate the location of the scene in the query image, and another the location of the place where the query image was taken. Location information is usually present for landmarks.

eaDescription :: Lens' EntityAnnotation (Maybe Text) Source #

Entity textual description, expressed in its locale language.

eaProperties :: Lens' EntityAnnotation [Property] Source #

Some entities can have additional optional Property fields. For example a different kind of score or string that qualifies the entity.

FeatureType

data FeatureType Source #

The feature type.

Constructors

TypeUnspecified

TYPE_UNSPECIFIED Unspecified feature type.

FaceDetection

FACE_DETECTION Run face detection.

LandmarkDetection

LANDMARK_DETECTION Run landmark detection.

LogoDetection

LOGO_DETECTION Run logo detection.

LabelDetection

LABEL_DETECTION Run label detection.

TextDetection

TEXT_DETECTION Run OCR.

SafeSearchDetection

SAFE_SEARCH_DETECTION Run various computer vision models to compute image safe-search properties.

ImageProperties

IMAGE_PROPERTIES Compute a set of properties about the image (such as the image's dominant colors).

Instances

Enum FeatureType Source # 
Eq FeatureType Source # 
Data FeatureType Source # 

Methods

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

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

toConstr :: FeatureType -> Constr #

dataTypeOf :: FeatureType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FeatureType Source # 
Read FeatureType Source # 
Show FeatureType Source # 
Generic FeatureType Source # 

Associated Types

type Rep FeatureType :: * -> * #

Hashable FeatureType Source # 
ToJSON FeatureType Source # 
FromJSON FeatureType Source # 
FromHttpApiData FeatureType Source # 
ToHttpApiData FeatureType Source # 
type Rep FeatureType Source # 
type Rep FeatureType = D1 (MetaData "FeatureType" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "TypeUnspecified" PrefixI False) U1) (C1 (MetaCons "FaceDetection" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LandmarkDetection" PrefixI False) U1) (C1 (MetaCons "LogoDetection" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "LabelDetection" PrefixI False) U1) (C1 (MetaCons "TextDetection" PrefixI False) U1)) ((:+:) (C1 (MetaCons "SafeSearchDetection" PrefixI False) U1) (C1 (MetaCons "ImageProperties" PrefixI False) U1))))

AnnotateImageRequest

data AnnotateImageRequest Source #

Request for performing Google Cloud Vision API tasks over a user-provided image, with user-requested features.

See: annotateImageRequest smart constructor.

Instances

Eq AnnotateImageRequest Source # 
Data AnnotateImageRequest Source # 

Methods

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

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

toConstr :: AnnotateImageRequest -> Constr #

dataTypeOf :: AnnotateImageRequest -> DataType #

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

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

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

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

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

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

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

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

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

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

Show AnnotateImageRequest Source # 
Generic AnnotateImageRequest Source # 
ToJSON AnnotateImageRequest Source # 
FromJSON AnnotateImageRequest Source # 
type Rep AnnotateImageRequest Source # 
type Rep AnnotateImageRequest = D1 (MetaData "AnnotateImageRequest" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "AnnotateImageRequest'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_airImage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Image))) ((:*:) (S1 (MetaSel (Just Symbol "_airFeatures") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Feature]))) (S1 (MetaSel (Just Symbol "_airImageContext") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ImageContext))))))

annotateImageRequest :: AnnotateImageRequest Source #

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

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

airImage :: Lens' AnnotateImageRequest (Maybe Image) Source #

The image to be processed.

airImageContext :: Lens' AnnotateImageRequest (Maybe ImageContext) Source #

Additional context that may accompany the image.

LandmarkType

data LandmarkType Source #

Face landmark type.

Constructors

UnknownLandmark

UNKNOWN_LANDMARK Unknown face landmark detected. Should not be filled.

LeftEye

LEFT_EYE Left eye.

RightEye

RIGHT_EYE Right eye.

LeftOfLeftEyebrow

LEFT_OF_LEFT_EYEBROW Left of left eyebrow.

RightOfLeftEyebrow

RIGHT_OF_LEFT_EYEBROW Right of left eyebrow.

LeftOfRightEyebrow

LEFT_OF_RIGHT_EYEBROW Left of right eyebrow.

RightOfRightEyebrow

RIGHT_OF_RIGHT_EYEBROW Right of right eyebrow.

MidpointBetweenEyes

MIDPOINT_BETWEEN_EYES Midpoint between eyes.

NoseTip

NOSE_TIP Nose tip.

UpperLip

UPPER_LIP Upper lip.

LowerLip

LOWER_LIP Lower lip.

MouthLeft

MOUTH_LEFT Mouth left.

MouthRight

MOUTH_RIGHT Mouth right.

MouthCenter

MOUTH_CENTER Mouth center.

NoseBottomRight

NOSE_BOTTOM_RIGHT Nose, bottom right.

NoseBottomLeft

NOSE_BOTTOM_LEFT Nose, bottom left.

NoseBottomCenter

NOSE_BOTTOM_CENTER Nose, bottom center.

LeftEyeTopBoundary

LEFT_EYE_TOP_BOUNDARY Left eye, top boundary.

LeftEyeRightCorner

LEFT_EYE_RIGHT_CORNER Left eye, right corner.

LeftEyeBottomBoundary

LEFT_EYE_BOTTOM_BOUNDARY Left eye, bottom boundary.

LeftEyeLeftCorner

LEFT_EYE_LEFT_CORNER Left eye, left corner.

RightEyeTopBoundary

RIGHT_EYE_TOP_BOUNDARY Right eye, top boundary.

RightEyeRightCorner

RIGHT_EYE_RIGHT_CORNER Right eye, right corner.

RightEyeBottomBoundary

RIGHT_EYE_BOTTOM_BOUNDARY Right eye, bottom boundary.

RightEyeLeftCorner

RIGHT_EYE_LEFT_CORNER Right eye, left corner.

LeftEyebrowUpperMidpoint

LEFT_EYEBROW_UPPER_MIDPOINT Left eyebrow, upper midpoint.

RightEyebrowUpperMidpoint

RIGHT_EYEBROW_UPPER_MIDPOINT Right eyebrow, upper midpoint.

LeftEarTragion

LEFT_EAR_TRAGION Left ear tragion.

RightEarTragion

RIGHT_EAR_TRAGION Right ear tragion.

LeftEyePupil

LEFT_EYE_PUPIL Left eye pupil.

RightEyePupil

RIGHT_EYE_PUPIL Right eye pupil.

ForeheadGlabella

FOREHEAD_GLABELLA Forehead glabella.

ChinGnathion

CHIN_GNATHION Chin gnathion.

ChinLeftGonion

CHIN_LEFT_GONION Chin left gonion.

ChinRightGonion

CHIN_RIGHT_GONION Chin right gonion.

Instances

Enum LandmarkType Source # 
Eq LandmarkType Source # 
Data LandmarkType Source # 

Methods

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

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

toConstr :: LandmarkType -> Constr #

dataTypeOf :: LandmarkType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LandmarkType Source # 
Read LandmarkType Source # 
Show LandmarkType Source # 
Generic LandmarkType Source # 

Associated Types

type Rep LandmarkType :: * -> * #

Hashable LandmarkType Source # 
ToJSON LandmarkType Source # 
FromJSON LandmarkType Source # 
FromHttpApiData LandmarkType Source # 
ToHttpApiData LandmarkType Source # 
type Rep LandmarkType Source # 
type Rep LandmarkType = D1 (MetaData "LandmarkType" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "UnknownLandmark" PrefixI False) U1) (C1 (MetaCons "LeftEye" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RightEye" PrefixI False) U1) (C1 (MetaCons "LeftOfLeftEyebrow" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "RightOfLeftEyebrow" PrefixI False) U1) (C1 (MetaCons "LeftOfRightEyebrow" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RightOfRightEyebrow" PrefixI False) U1) (C1 (MetaCons "MidpointBetweenEyes" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "NoseTip" PrefixI False) U1) (C1 (MetaCons "UpperLip" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LowerLip" PrefixI False) U1) (C1 (MetaCons "MouthLeft" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "MouthRight" PrefixI False) U1) (C1 (MetaCons "MouthCenter" PrefixI False) U1)) ((:+:) (C1 (MetaCons "NoseBottomRight" PrefixI False) U1) ((:+:) (C1 (MetaCons "NoseBottomLeft" PrefixI False) U1) (C1 (MetaCons "NoseBottomCenter" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "LeftEyeTopBoundary" PrefixI False) U1) (C1 (MetaCons "LeftEyeRightCorner" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LeftEyeBottomBoundary" PrefixI False) U1) (C1 (MetaCons "LeftEyeLeftCorner" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "RightEyeTopBoundary" PrefixI False) U1) (C1 (MetaCons "RightEyeRightCorner" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RightEyeBottomBoundary" PrefixI False) U1) ((:+:) (C1 (MetaCons "RightEyeLeftCorner" PrefixI False) U1) (C1 (MetaCons "LeftEyebrowUpperMidpoint" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "RightEyebrowUpperMidpoint" PrefixI False) U1) (C1 (MetaCons "LeftEarTragion" PrefixI False) U1)) ((:+:) (C1 (MetaCons "RightEarTragion" PrefixI False) U1) (C1 (MetaCons "LeftEyePupil" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "RightEyePupil" PrefixI False) U1) (C1 (MetaCons "ForeheadGlabella" PrefixI False) U1)) ((:+:) (C1 (MetaCons "ChinGnathion" PrefixI False) U1) ((:+:) (C1 (MetaCons "ChinLeftGonion" PrefixI False) U1) (C1 (MetaCons "ChinRightGonion" PrefixI False) U1)))))))

Xgafv

data Xgafv Source #

V1 error format.

Constructors

X1

1 v1 error format

X2

2 v2 error format

Instances

Enum Xgafv Source # 
Eq Xgafv Source # 

Methods

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

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

Data Xgafv Source # 

Methods

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

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

toConstr :: Xgafv -> Constr #

dataTypeOf :: Xgafv -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Xgafv Source # 

Methods

compare :: Xgafv -> Xgafv -> Ordering #

(<) :: Xgafv -> Xgafv -> Bool #

(<=) :: Xgafv -> Xgafv -> Bool #

(>) :: Xgafv -> Xgafv -> Bool #

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

max :: Xgafv -> Xgafv -> Xgafv #

min :: Xgafv -> Xgafv -> Xgafv #

Read Xgafv Source # 
Show Xgafv Source # 

Methods

showsPrec :: Int -> Xgafv -> ShowS #

show :: Xgafv -> String #

showList :: [Xgafv] -> ShowS #

Generic Xgafv Source # 

Associated Types

type Rep Xgafv :: * -> * #

Methods

from :: Xgafv -> Rep Xgafv x #

to :: Rep Xgafv x -> Xgafv #

Hashable Xgafv Source # 

Methods

hashWithSalt :: Int -> Xgafv -> Int #

hash :: Xgafv -> Int #

ToJSON Xgafv Source # 
FromJSON Xgafv Source # 
FromHttpApiData Xgafv Source # 
ToHttpApiData Xgafv Source # 
type Rep Xgafv Source # 
type Rep Xgafv = D1 (MetaData "Xgafv" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) (C1 (MetaCons "X1" PrefixI False) U1) (C1 (MetaCons "X2" PrefixI False) U1))

ImageSource

data ImageSource Source #

External image source (Google Cloud Storage image location).

See: imageSource smart constructor.

Instances

Eq ImageSource Source # 
Data ImageSource Source # 

Methods

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

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

toConstr :: ImageSource -> Constr #

dataTypeOf :: ImageSource -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ImageSource Source # 
Generic ImageSource Source # 

Associated Types

type Rep ImageSource :: * -> * #

ToJSON ImageSource Source # 
FromJSON ImageSource Source # 
type Rep ImageSource Source # 
type Rep ImageSource = D1 (MetaData "ImageSource" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" True) (C1 (MetaCons "ImageSource'" PrefixI True) (S1 (MetaSel (Just Symbol "_isGcsImageURI") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe Text))))

imageSource :: ImageSource Source #

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

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

isGcsImageURI :: Lens' ImageSource (Maybe Text) Source #

Google Cloud Storage image URI. It must be in the following form: `gs://bucket_name/object_name`. For more details, please see: https://cloud.google.com/storage/docs/reference-uris. NOTE: Cloud Storage object versioning is not supported!

SafeSearchAnnotationSpoof

data SafeSearchAnnotationSpoof Source #

Spoof likelihood. The likelihood that an obvious modification was made to the image's canonical version to make it appear funny or offensive.

Constructors

SSASUnknown

UNKNOWN Unknown likelihood.

SSASVeryUnlikely

VERY_UNLIKELY The image very unlikely belongs to the vertical specified.

SSASUnlikely

UNLIKELY The image unlikely belongs to the vertical specified.

SSASPossible

POSSIBLE The image possibly belongs to the vertical specified.

SSASLikely

LIKELY The image likely belongs to the vertical specified.

SSASVeryLikely

VERY_LIKELY The image very likely belongs to the vertical specified.

Instances

Enum SafeSearchAnnotationSpoof Source # 
Eq SafeSearchAnnotationSpoof Source # 
Data SafeSearchAnnotationSpoof Source # 

Methods

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

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

toConstr :: SafeSearchAnnotationSpoof -> Constr #

dataTypeOf :: SafeSearchAnnotationSpoof -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SafeSearchAnnotationSpoof Source # 
Read SafeSearchAnnotationSpoof Source # 
Show SafeSearchAnnotationSpoof Source # 
Generic SafeSearchAnnotationSpoof Source # 
Hashable SafeSearchAnnotationSpoof Source # 
ToJSON SafeSearchAnnotationSpoof Source # 
FromJSON SafeSearchAnnotationSpoof Source # 
FromHttpApiData SafeSearchAnnotationSpoof Source # 
ToHttpApiData SafeSearchAnnotationSpoof Source # 
type Rep SafeSearchAnnotationSpoof Source # 
type Rep SafeSearchAnnotationSpoof = D1 (MetaData "SafeSearchAnnotationSpoof" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) (C1 (MetaCons "SSASUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "SSASVeryUnlikely" PrefixI False) U1) (C1 (MetaCons "SSASUnlikely" PrefixI False) U1))) ((:+:) (C1 (MetaCons "SSASPossible" PrefixI False) U1) ((:+:) (C1 (MetaCons "SSASLikely" PrefixI False) U1) (C1 (MetaCons "SSASVeryLikely" PrefixI False) U1))))

FaceAnnotationSurpriseLikelihood

data FaceAnnotationSurpriseLikelihood Source #

Surprise likelihood.

Constructors

FASLUnknown

UNKNOWN Unknown likelihood.

FASLVeryUnlikely

VERY_UNLIKELY The image very unlikely belongs to the vertical specified.

FASLUnlikely

UNLIKELY The image unlikely belongs to the vertical specified.

FASLPossible

POSSIBLE The image possibly belongs to the vertical specified.

FASLLikely

LIKELY The image likely belongs to the vertical specified.

FASLVeryLikely

VERY_LIKELY The image very likely belongs to the vertical specified.

Instances

Enum FaceAnnotationSurpriseLikelihood Source # 
Eq FaceAnnotationSurpriseLikelihood Source # 
Data FaceAnnotationSurpriseLikelihood Source # 

Methods

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

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

toConstr :: FaceAnnotationSurpriseLikelihood -> Constr #

dataTypeOf :: FaceAnnotationSurpriseLikelihood -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FaceAnnotationSurpriseLikelihood Source # 
Read FaceAnnotationSurpriseLikelihood Source # 
Show FaceAnnotationSurpriseLikelihood Source # 
Generic FaceAnnotationSurpriseLikelihood Source # 
Hashable FaceAnnotationSurpriseLikelihood Source # 
ToJSON FaceAnnotationSurpriseLikelihood Source # 
FromJSON FaceAnnotationSurpriseLikelihood Source # 
FromHttpApiData FaceAnnotationSurpriseLikelihood Source # 
ToHttpApiData FaceAnnotationSurpriseLikelihood Source # 
type Rep FaceAnnotationSurpriseLikelihood Source # 
type Rep FaceAnnotationSurpriseLikelihood = D1 (MetaData "FaceAnnotationSurpriseLikelihood" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) (C1 (MetaCons "FASLUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "FASLVeryUnlikely" PrefixI False) U1) (C1 (MetaCons "FASLUnlikely" PrefixI False) U1))) ((:+:) (C1 (MetaCons "FASLPossible" PrefixI False) U1) ((:+:) (C1 (MetaCons "FASLLikely" PrefixI False) U1) (C1 (MetaCons "FASLVeryLikely" PrefixI False) U1))))

SafeSearchAnnotation

data SafeSearchAnnotation Source #

Set of features pertaining to the image, computed by various computer vision methods over safe-search verticals (for example, adult, spoof, medical, violence).

See: safeSearchAnnotation smart constructor.

Instances

Eq SafeSearchAnnotation Source # 
Data SafeSearchAnnotation Source # 

Methods

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

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

toConstr :: SafeSearchAnnotation -> Constr #

dataTypeOf :: SafeSearchAnnotation -> DataType #

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

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

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

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

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

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

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

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

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

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

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

safeSearchAnnotation :: SafeSearchAnnotation Source #

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

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

ssaSpoof :: Lens' SafeSearchAnnotation (Maybe SafeSearchAnnotationSpoof) Source #

Spoof likelihood. The likelihood that an obvious modification was made to the image's canonical version to make it appear funny or offensive.

ssaAdult :: Lens' SafeSearchAnnotation (Maybe SafeSearchAnnotationAdult) Source #

Represents the adult contents likelihood for the image.

FaceAnnotationSorrowLikelihood

data FaceAnnotationSorrowLikelihood Source #

Sorrow likelihood.

Constructors

FUnknown

UNKNOWN Unknown likelihood.

FVeryUnlikely

VERY_UNLIKELY The image very unlikely belongs to the vertical specified.

FUnlikely

UNLIKELY The image unlikely belongs to the vertical specified.

FPossible

POSSIBLE The image possibly belongs to the vertical specified.

FLikely

LIKELY The image likely belongs to the vertical specified.

FVeryLikely

VERY_LIKELY The image very likely belongs to the vertical specified.

Instances

Enum FaceAnnotationSorrowLikelihood Source # 
Eq FaceAnnotationSorrowLikelihood Source # 
Data FaceAnnotationSorrowLikelihood Source # 

Methods

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

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

toConstr :: FaceAnnotationSorrowLikelihood -> Constr #

dataTypeOf :: FaceAnnotationSorrowLikelihood -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FaceAnnotationSorrowLikelihood Source # 
Read FaceAnnotationSorrowLikelihood Source # 
Show FaceAnnotationSorrowLikelihood Source # 
Generic FaceAnnotationSorrowLikelihood Source # 
Hashable FaceAnnotationSorrowLikelihood Source # 
ToJSON FaceAnnotationSorrowLikelihood Source # 
FromJSON FaceAnnotationSorrowLikelihood Source # 
FromHttpApiData FaceAnnotationSorrowLikelihood Source # 
ToHttpApiData FaceAnnotationSorrowLikelihood Source # 
type Rep FaceAnnotationSorrowLikelihood Source # 
type Rep FaceAnnotationSorrowLikelihood = D1 (MetaData "FaceAnnotationSorrowLikelihood" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) (C1 (MetaCons "FUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "FVeryUnlikely" PrefixI False) U1) (C1 (MetaCons "FUnlikely" PrefixI False) U1))) ((:+:) (C1 (MetaCons "FPossible" PrefixI False) U1) ((:+:) (C1 (MetaCons "FLikely" PrefixI False) U1) (C1 (MetaCons "FVeryLikely" PrefixI False) U1))))

FaceAnnotationJoyLikelihood

data FaceAnnotationJoyLikelihood Source #

Joy likelihood.

Constructors

FAJLUnknown

UNKNOWN Unknown likelihood.

FAJLVeryUnlikely

VERY_UNLIKELY The image very unlikely belongs to the vertical specified.

FAJLUnlikely

UNLIKELY The image unlikely belongs to the vertical specified.

FAJLPossible

POSSIBLE The image possibly belongs to the vertical specified.

FAJLLikely

LIKELY The image likely belongs to the vertical specified.

FAJLVeryLikely

VERY_LIKELY The image very likely belongs to the vertical specified.

Instances

Enum FaceAnnotationJoyLikelihood Source # 
Eq FaceAnnotationJoyLikelihood Source # 
Data FaceAnnotationJoyLikelihood Source # 

Methods

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

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

toConstr :: FaceAnnotationJoyLikelihood -> Constr #

dataTypeOf :: FaceAnnotationJoyLikelihood -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FaceAnnotationJoyLikelihood Source # 
Read FaceAnnotationJoyLikelihood Source # 
Show FaceAnnotationJoyLikelihood Source # 
Generic FaceAnnotationJoyLikelihood Source # 
Hashable FaceAnnotationJoyLikelihood Source # 
ToJSON FaceAnnotationJoyLikelihood Source # 
FromJSON FaceAnnotationJoyLikelihood Source # 
FromHttpApiData FaceAnnotationJoyLikelihood Source # 
ToHttpApiData FaceAnnotationJoyLikelihood Source # 
type Rep FaceAnnotationJoyLikelihood Source # 
type Rep FaceAnnotationJoyLikelihood = D1 (MetaData "FaceAnnotationJoyLikelihood" "Network.Google.Vision.Types.Sum" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) ((:+:) ((:+:) (C1 (MetaCons "FAJLUnknown" PrefixI False) U1) ((:+:) (C1 (MetaCons "FAJLVeryUnlikely" PrefixI False) U1) (C1 (MetaCons "FAJLUnlikely" PrefixI False) U1))) ((:+:) (C1 (MetaCons "FAJLPossible" PrefixI False) U1) ((:+:) (C1 (MetaCons "FAJLLikely" PrefixI False) U1) (C1 (MetaCons "FAJLVeryLikely" PrefixI False) U1))))

ImageContext

data ImageContext Source #

Image context.

See: imageContext smart constructor.

Instances

Eq ImageContext Source # 
Data ImageContext Source # 

Methods

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

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

toConstr :: ImageContext -> Constr #

dataTypeOf :: ImageContext -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ImageContext Source # 
Generic ImageContext Source # 

Associated Types

type Rep ImageContext :: * -> * #

ToJSON ImageContext Source # 
FromJSON ImageContext Source # 
type Rep ImageContext Source # 
type Rep ImageContext = D1 (MetaData "ImageContext" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "ImageContext'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_icLanguageHints") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [Text]))) (S1 (MetaSel (Just Symbol "_icLatLongRect") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LatLongRect)))))

imageContext :: ImageContext Source #

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

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

icLanguageHints :: Lens' ImageContext [Text] Source #

List of languages to use for TEXT_DETECTION. In most cases, an empty value yields the best results since it enables automatic language detection. For languages based on the Latin alphabet, setting `language_hints` is not needed. In rare cases, when the language of the text in the image is known, setting a hint will help get better results (although it will be a significant hindrance if the hint is wrong). Text detection returns an error if one or more of the specified languages is not one of the supported languages.

icLatLongRect :: Lens' ImageContext (Maybe LatLongRect) Source #

Lat/long rectangle that specifies the location of the image.

DominantColorsAnnotation

data DominantColorsAnnotation Source #

Set of dominant colors and their corresponding scores.

See: dominantColorsAnnotation smart constructor.

Instances

Eq DominantColorsAnnotation Source # 
Data DominantColorsAnnotation Source # 

Methods

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

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

toConstr :: DominantColorsAnnotation -> Constr #

dataTypeOf :: DominantColorsAnnotation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show DominantColorsAnnotation Source # 
Generic DominantColorsAnnotation Source # 
ToJSON DominantColorsAnnotation Source # 
FromJSON DominantColorsAnnotation Source # 
type Rep DominantColorsAnnotation Source # 
type Rep DominantColorsAnnotation = D1 (MetaData "DominantColorsAnnotation" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" True) (C1 (MetaCons "DominantColorsAnnotation'" PrefixI True) (S1 (MetaSel (Just Symbol "_dcaColors") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [ColorInfo]))))

dominantColorsAnnotation :: DominantColorsAnnotation Source #

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

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

dcaColors :: Lens' DominantColorsAnnotation [ColorInfo] Source #

RGB color values, with their score and pixel fraction.

LatLongRect

data LatLongRect Source #

Rectangle determined by min and max LatLng pairs.

See: latLongRect smart constructor.

Instances

Eq LatLongRect Source # 
Data LatLongRect Source # 

Methods

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

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

toConstr :: LatLongRect -> Constr #

dataTypeOf :: LatLongRect -> DataType #

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

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

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

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

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

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

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

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

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

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

Show LatLongRect Source # 
Generic LatLongRect Source # 

Associated Types

type Rep LatLongRect :: * -> * #

ToJSON LatLongRect Source # 
FromJSON LatLongRect Source # 
type Rep LatLongRect Source # 
type Rep LatLongRect = D1 (MetaData "LatLongRect" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "LatLongRect'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_llrMaxLatLng") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LatLng))) (S1 (MetaSel (Just Symbol "_llrMinLatLng") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe LatLng)))))

latLongRect :: LatLongRect Source #

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

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

BatchAnnotateImagesResponse

data BatchAnnotateImagesResponse Source #

Response to a batch image annotation request.

See: batchAnnotateImagesResponse smart constructor.

Instances

Eq BatchAnnotateImagesResponse Source # 
Data BatchAnnotateImagesResponse Source # 

Methods

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

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

toConstr :: BatchAnnotateImagesResponse -> Constr #

dataTypeOf :: BatchAnnotateImagesResponse -> DataType #

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

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

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

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

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

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

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

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

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

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

Show BatchAnnotateImagesResponse Source # 
Generic BatchAnnotateImagesResponse Source # 
ToJSON BatchAnnotateImagesResponse Source # 
FromJSON BatchAnnotateImagesResponse Source # 
type Rep BatchAnnotateImagesResponse Source # 
type Rep BatchAnnotateImagesResponse = D1 (MetaData "BatchAnnotateImagesResponse" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" True) (C1 (MetaCons "BatchAnnotateImagesResponse'" PrefixI True) (S1 (MetaSel (Just Symbol "_bairResponses") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (Maybe [AnnotateImageResponse]))))

batchAnnotateImagesResponse :: BatchAnnotateImagesResponse Source #

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

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

bairResponses :: Lens' BatchAnnotateImagesResponse [AnnotateImageResponse] Source #

Individual responses to image annotation requests within the batch.

Position

data Position Source #

A 3D position in the image, used primarily for Face detection landmarks. A valid Position must have both x and y coordinates. The position coordinates are in the same scale as the original image.

See: position smart constructor.

Instances

Eq Position Source # 
Data Position Source # 

Methods

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

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

toConstr :: Position -> Constr #

dataTypeOf :: Position -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Position Source # 
Generic Position Source # 

Associated Types

type Rep Position :: * -> * #

Methods

from :: Position -> Rep Position x #

to :: Rep Position x -> Position #

ToJSON Position Source # 
FromJSON Position Source # 
type Rep Position Source # 
type Rep Position = D1 (MetaData "Position" "Network.Google.Vision.Types.Product" "gogol-vision-0.1.1-HZweVQokUBLIAySNBzMbNB" False) (C1 (MetaCons "Position'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_pZ") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) ((:*:) (S1 (MetaSel (Just Symbol "_pX") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_pY") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))))))

position :: Position Source #

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

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

pZ :: Lens' Position (Maybe Double) Source #

Z coordinate (or depth).

pX :: Lens' Position (Maybe Double) Source #

X coordinate.

pY :: Lens' Position (Maybe Double) Source #

Y coordinate.