gogol-customsearch-0.4.0: Google CustomSearch 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.CustomSearch.Types

Contents

Description

 
Synopsis

Service Configuration

customSearchService :: ServiceConfig Source #

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

CSEListImgType

data CSEListImgType Source #

Returns images of a type, which can be one of: clipart, face, lineart, news, and photo.

Constructors

CliPart

clipart clipart

Face

face face

Lineart

lineart lineart

News

news news

Photo

photo photo

Instances
Enum CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSEListImgType -> Constr #

dataTypeOf :: CSEListImgType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSEListImgType :: Type -> Type #

Hashable CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListImgType = D1 (MetaData "CSEListImgType" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) ((C1 (MetaCons "CliPart" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Face" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Lineart" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "News" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Photo" PrefixI False) (U1 :: Type -> Type))))

PromotionImage

data PromotionImage Source #

Instances
Eq PromotionImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Data PromotionImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: PromotionImage -> Constr #

dataTypeOf :: PromotionImage -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PromotionImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic PromotionImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep PromotionImage :: Type -> Type #

ToJSON PromotionImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON PromotionImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep PromotionImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep PromotionImage = D1 (MetaData "PromotionImage" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "PromotionImage'" PrefixI True) (S1 (MetaSel (Just "_piHeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: (S1 (MetaSel (Just "_piWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_piSource") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

promotionImage :: PromotionImage Source #

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

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

Context

data Context Source #

Instances
Eq Context Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

Data Context Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: Context -> Constr #

dataTypeOf :: Context -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Context Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic Context Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep Context :: Type -> Type #

Methods

from :: Context -> Rep Context x #

to :: Rep Context x -> Context #

ToJSON Context Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON Context Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep Context Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep Context = D1 (MetaData "Context" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "Context'" PrefixI True) (S1 (MetaSel (Just "_cFacets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [[ContextFacetsItemItem]])) :*: S1 (MetaSel (Just "_cTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

context :: Context Source #

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

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

CSEListSiteSearchFilter

data CSEListSiteSearchFilter Source #

Controls whether to include or exclude results from the site named in the as_sitesearch parameter

Constructors

E

e exclude

I

i include

Instances
Enum CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSEListSiteSearchFilter -> Constr #

dataTypeOf :: CSEListSiteSearchFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSEListSiteSearchFilter :: Type -> Type #

Hashable CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListSiteSearchFilter = D1 (MetaData "CSEListSiteSearchFilter" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "E" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "I" PrefixI False) (U1 :: Type -> Type))

SearchQueries

data SearchQueries Source #

Instances
Eq SearchQueries Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Data SearchQueries Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: SearchQueries -> Constr #

dataTypeOf :: SearchQueries -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SearchQueries Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic SearchQueries Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep SearchQueries :: Type -> Type #

ToJSON SearchQueries Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON SearchQueries Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep SearchQueries Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep SearchQueries = D1 (MetaData "SearchQueries" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" True) (C1 (MetaCons "SearchQueries'" PrefixI True) (S1 (MetaSel (Just "_sqAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text [Query]))))

searchQueries Source #

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

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

ResultPagemapAdditionalItem

data ResultPagemapAdditionalItem Source #

Instances
Eq ResultPagemapAdditionalItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Data ResultPagemapAdditionalItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: ResultPagemapAdditionalItem -> Constr #

dataTypeOf :: ResultPagemapAdditionalItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ResultPagemapAdditionalItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic ResultPagemapAdditionalItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep ResultPagemapAdditionalItem :: Type -> Type #

ToJSON ResultPagemapAdditionalItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON ResultPagemapAdditionalItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep ResultPagemapAdditionalItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep ResultPagemapAdditionalItem = D1 (MetaData "ResultPagemapAdditionalItem" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" True) (C1 (MetaCons "ResultPagemapAdditionalItem'" PrefixI True) (S1 (MetaSel (Just "_rpaiAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text JSONValue))))

resultPagemapAdditionalItem Source #

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

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

SearchURL

data SearchURL Source #

Instances
Eq SearchURL Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Data SearchURL Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: SearchURL -> Constr #

dataTypeOf :: SearchURL -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SearchURL Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic SearchURL Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep SearchURL :: Type -> Type #

ToJSON SearchURL Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON SearchURL Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep SearchURL Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep SearchURL = D1 (MetaData "SearchURL" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "SearchURL'" PrefixI True) (S1 (MetaSel (Just "_suType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text) :*: S1 (MetaSel (Just "_suTemplate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))

searchURL :: SearchURL Source #

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

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

CSESiterestrictListFilter

data CSESiterestrictListFilter Source #

Controls turning on or off the duplicate content filter.

Constructors

CSESLF0

0 Turns off duplicate content filter.

CSESLF1

1 Turns on duplicate content filter.

Instances
Enum CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSESiterestrictListFilter -> Constr #

dataTypeOf :: CSESiterestrictListFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSESiterestrictListFilter :: Type -> Type #

Hashable CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListFilter = D1 (MetaData "CSESiterestrictListFilter" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "CSESLF0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLF1" PrefixI False) (U1 :: Type -> Type))

SearchSpelling

data SearchSpelling Source #

Instances
Eq SearchSpelling Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Data SearchSpelling Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: SearchSpelling -> Constr #

dataTypeOf :: SearchSpelling -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SearchSpelling Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic SearchSpelling Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep SearchSpelling :: Type -> Type #

ToJSON SearchSpelling Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON SearchSpelling Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep SearchSpelling Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep SearchSpelling = D1 (MetaData "SearchSpelling" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "SearchSpelling'" PrefixI True) (S1 (MetaSel (Just "_ssCorrectedQuery") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_ssHTMLCorrectedQuery") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))

searchSpelling :: SearchSpelling Source #

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

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

CSESiterestrictListImgType

data CSESiterestrictListImgType Source #

Returns images of a type, which can be one of: clipart, face, lineart, news, and photo.

Constructors

CSESLITCliPart

clipart clipart

CSESLITFace

face face

CSESLITLineart

lineart lineart

CSESLITNews

news news

CSESLITPhoto

photo photo

Instances
Enum CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSESiterestrictListImgType -> Constr #

dataTypeOf :: CSESiterestrictListImgType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSESiterestrictListImgType :: Type -> Type #

Hashable CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListImgType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListImgType = D1 (MetaData "CSESiterestrictListImgType" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) ((C1 (MetaCons "CSESLITCliPart" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLITFace" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CSESLITLineart" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSESLITNews" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLITPhoto" PrefixI False) (U1 :: Type -> Type))))

CSEListImgDominantColor

data CSEListImgDominantColor Source #

Returns images of a specific dominant color: red, orange, yellow, green, teal, blue, purple, pink, white, gray, black and brown.

Constructors

Black

black black

Blue

blue blue

Brown

brown brown

Gray

gray gray

Green

green green

Orange

orange orange

Pink

pink pink

Purple

purple purple

Red

red red

Teal

teal teal

White

white white

Yellow

yellow yellow

Instances
Enum CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSEListImgDominantColor -> Constr #

dataTypeOf :: CSEListImgDominantColor -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSEListImgDominantColor :: Type -> Type #

Hashable CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListImgDominantColor = D1 (MetaData "CSEListImgDominantColor" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (((C1 (MetaCons "Black" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Blue" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Brown" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Gray" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Green" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Orange" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "Pink" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "Purple" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Red" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "Teal" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "White" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Yellow" PrefixI False) (U1 :: Type -> Type)))))

ResultImage

data ResultImage Source #

Instances
Eq ResultImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Data ResultImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: ResultImage -> Constr #

dataTypeOf :: ResultImage -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ResultImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic ResultImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep ResultImage :: Type -> Type #

ToJSON ResultImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON ResultImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep ResultImage Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep ResultImage = D1 (MetaData "ResultImage" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "ResultImage'" PrefixI True) ((S1 (MetaSel (Just "_riThumbnailLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_riHeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_riByteSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))) :*: ((S1 (MetaSel (Just "_riContextLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_riThumbnailHeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) :*: (S1 (MetaSel (Just "_riWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_riThumbnailWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))))))

resultImage :: ResultImage Source #

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

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

CSEListSafe

data CSEListSafe Source #

Search safety level

Constructors

Active

active Enables safe search filtering.

High

high (Deprecated) Same as active.

Medium

medium (Deprecated) Same as active.

Off

off Disables safe search filtering.

Instances
Enum CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSEListSafe -> Constr #

dataTypeOf :: CSEListSafe -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSEListSafe :: Type -> Type #

Hashable CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListSafe = D1 (MetaData "CSEListSafe" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) ((C1 (MetaCons "Active" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "High" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "Medium" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "Off" PrefixI False) (U1 :: Type -> Type)))

CSESiterestrictListImgSize

data CSESiterestrictListImgSize Source #

Returns images of a specified size, where size can be one of: icon, small, medium, large, xlarge, xxlarge, and huge.

Constructors

CSESLISHuge

huge huge

CSESLISIcon

icon icon

CSESLISLarge

large large

CSESLISMedium

medium medium

CSESLISSmall

small small

CSESLISXlarge

xlarge xlarge

CSESLISXxlarge

xxlarge xxlarge

Instances
Enum CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSESiterestrictListImgSize -> Constr #

dataTypeOf :: CSESiterestrictListImgSize -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSESiterestrictListImgSize :: Type -> Type #

Hashable CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListImgSize = D1 (MetaData "CSESiterestrictListImgSize" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) ((C1 (MetaCons "CSESLISHuge" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSESLISIcon" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLISLarge" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CSESLISMedium" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLISSmall" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CSESLISXlarge" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLISXxlarge" PrefixI False) (U1 :: Type -> Type))))

ResultPagemap

data ResultPagemap Source #

Instances
Eq ResultPagemap Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Data ResultPagemap Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: ResultPagemap -> Constr #

dataTypeOf :: ResultPagemap -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ResultPagemap Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic ResultPagemap Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep ResultPagemap :: Type -> Type #

ToJSON ResultPagemap Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON ResultPagemap Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep ResultPagemap Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep ResultPagemap = D1 (MetaData "ResultPagemap" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" True) (C1 (MetaCons "ResultPagemap'" PrefixI True) (S1 (MetaSel (Just "_rpAddtional") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashMap Text [ResultPagemapAdditionalItem]))))

resultPagemap Source #

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

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

CSESiterestrictListImgColorType

data CSESiterestrictListImgColorType Source #

Returns black and white, grayscale, or color images: mono, gray, and color.

Constructors

CSESLICTColor

color color

CSESLICTGray

gray gray

CSESLICTMono

mono mono

Instances
Enum CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSESiterestrictListImgColorType -> Constr #

dataTypeOf :: CSESiterestrictListImgColorType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSESiterestrictListImgColorType :: Type -> Type #

Hashable CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListImgColorType = D1 (MetaData "CSESiterestrictListImgColorType" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "CSESLICTColor" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSESLICTGray" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLICTMono" PrefixI False) (U1 :: Type -> Type)))

CSEListImgColorType

data CSEListImgColorType Source #

Returns black and white, grayscale, or color images: mono, gray, and color.

Constructors

CSELICTColor

color color

CSELICTGray

gray gray

CSELICTMono

mono mono

Instances
Enum CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSEListImgColorType -> Constr #

dataTypeOf :: CSEListImgColorType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSEListImgColorType :: Type -> Type #

Hashable CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListImgColorType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListImgColorType = D1 (MetaData "CSEListImgColorType" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "CSELICTColor" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSELICTGray" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELICTMono" PrefixI False) (U1 :: Type -> Type)))

CSESiterestrictListSafe

data CSESiterestrictListSafe Source #

Search safety level

Constructors

CSESLSHigh

high Enables highest level of safe search filtering.

CSESLSMedium

medium Enables moderate safe search filtering.

CSESLSOff

off Disables safe search filtering.

Instances
Enum CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSESiterestrictListSafe -> Constr #

dataTypeOf :: CSESiterestrictListSafe -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSESiterestrictListSafe :: Type -> Type #

Hashable CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListSafe Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListSafe = D1 (MetaData "CSESiterestrictListSafe" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "CSESLSHigh" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSESLSMedium" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLSOff" PrefixI False) (U1 :: Type -> Type)))

Result

data Result Source #

Instances
Eq Result Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

Data Result Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: Result -> Constr #

dataTypeOf :: Result -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Result Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic Result Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep Result :: Type -> Type #

Methods

from :: Result -> Rep Result x #

to :: Rep Result x -> Result #

ToJSON Result Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON Result Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep Result Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep Result = D1 (MetaData "Result" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "Result'" PrefixI True) (((S1 (MetaSel (Just "_rMime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rImage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ResultImage)) :*: S1 (MetaSel (Just "_rPagemap") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ResultPagemap)))) :*: ((S1 (MetaSel (Just "_rDisplayLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rFileFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_rSnippet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) :*: (((S1 (MetaSel (Just "_rLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rHTMLSnippet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_rHTMLFormattedURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rCacheId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_rFormattedURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rHTMLTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_rLabels") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ResultLabelsItem])) :*: S1 (MetaSel (Just "_rTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

result :: Result Source #

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

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

ResultLabelsItem

data ResultLabelsItem Source #

Instances
Eq ResultLabelsItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Data ResultLabelsItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: ResultLabelsItem -> Constr #

dataTypeOf :: ResultLabelsItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ResultLabelsItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic ResultLabelsItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep ResultLabelsItem :: Type -> Type #

ToJSON ResultLabelsItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON ResultLabelsItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep ResultLabelsItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep ResultLabelsItem = D1 (MetaData "ResultLabelsItem" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "ResultLabelsItem'" PrefixI True) (S1 (MetaSel (Just "_rliName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_rliDisplayName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_rliLabelWithOp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

resultLabelsItem :: ResultLabelsItem Source #

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

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

CSESiterestrictListImgDominantColor

data CSESiterestrictListImgDominantColor Source #

Returns images of a specific dominant color: red, orange, yellow, green, teal, blue, purple, pink, white, gray, black and brown.

Constructors

CSESLIDCBlack

black black

CSESLIDCBlue

blue blue

CSESLIDCBrown

brown brown

CSESLIDCGray

gray gray

CSESLIDCGreen

green green

CSESLIDCOrange

orange orange

CSESLIDCPink

pink pink

CSESLIDCPurple

purple purple

CSESLIDCRed

red red

CSESLIDCTeal

teal teal

CSESLIDCWhite

white white

CSESLIDCYellow

yellow yellow

Instances
Enum CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSESiterestrictListImgDominantColor -> Constr #

dataTypeOf :: CSESiterestrictListImgDominantColor -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Hashable CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListImgDominantColor Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListImgDominantColor = D1 (MetaData "CSESiterestrictListImgDominantColor" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (((C1 (MetaCons "CSESLIDCBlack" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSESLIDCBlue" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLIDCBrown" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "CSESLIDCGray" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSESLIDCGreen" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLIDCOrange" PrefixI False) (U1 :: Type -> Type)))) :+: ((C1 (MetaCons "CSESLIDCPink" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSESLIDCPurple" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLIDCRed" PrefixI False) (U1 :: Type -> Type))) :+: (C1 (MetaCons "CSESLIDCTeal" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSESLIDCWhite" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLIDCYellow" PrefixI False) (U1 :: Type -> Type)))))

SearchSearchInformation

data SearchSearchInformation Source #

Instances
Eq SearchSearchInformation Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Data SearchSearchInformation Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: SearchSearchInformation -> Constr #

dataTypeOf :: SearchSearchInformation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SearchSearchInformation Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic SearchSearchInformation Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep SearchSearchInformation :: Type -> Type #

ToJSON SearchSearchInformation Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON SearchSearchInformation Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep SearchSearchInformation Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep SearchSearchInformation = D1 (MetaData "SearchSearchInformation" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "SearchSearchInformation'" PrefixI True) ((S1 (MetaSel (Just "_ssiSearchTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))) :*: S1 (MetaSel (Just "_ssiFormattedSearchTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_ssiTotalResults") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))) :*: S1 (MetaSel (Just "_ssiFormattedTotalResults") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

searchSearchInformation :: SearchSearchInformation Source #

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

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

CSEListFilter

data CSEListFilter Source #

Controls turning on or off the duplicate content filter.

Constructors

CSELF0

0 Turns off duplicate content filter.

CSELF1

1 Turns on duplicate content filter.

Instances
Enum CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSEListFilter -> Constr #

dataTypeOf :: CSEListFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSEListFilter :: Type -> Type #

Hashable CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListFilter = D1 (MetaData "CSEListFilter" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "CSELF0" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELF1" PrefixI False) (U1 :: Type -> Type))

Query

data Query Source #

Instances
Eq Query Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

Data Query Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: Query -> Constr #

dataTypeOf :: Query -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Query Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Generic Query Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep Query :: Type -> Type #

Methods

from :: Query -> Rep Query x #

to :: Rep Query x -> Query #

ToJSON Query Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON Query Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep Query Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep Query = D1 (MetaData "Query" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "Query'" PrefixI True) (((((S1 (MetaSel (Just "_qImgDominantColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qOutputEncoding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_qSiteSearchFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qInputEncoding") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_qOrTerms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qSearchTerms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_qStartPage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: (S1 (MetaSel (Just "_qRights") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qCount") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))) :*: (((S1 (MetaSel (Just "_qExcludeTerms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qFileType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_qSearchType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qGoogleHost") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_qDisableCnTwTranslation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qRelatedSite") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_qHl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_qSort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qLanguage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))) :*: ((((S1 (MetaSel (Just "_qSiteSearch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_qTotalResults") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64))) :*: S1 (MetaSel (Just "_qDateRestrict") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_qTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qLinkSite") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_qLowRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_qImgType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qGl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) :*: (((S1 (MetaSel (Just "_qCx") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qImgColorType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_qImgSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qExactTerms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) :*: ((S1 (MetaSel (Just "_qStartIndex") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))) :*: S1 (MetaSel (Just "_qCr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_qSafe") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_qHq") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_qHighRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))))

CSESiterestrictListSiteSearchFilter

data CSESiterestrictListSiteSearchFilter Source #

Controls whether to include or exclude results from the site named in the as_sitesearch parameter

Constructors

CSESLSSFE

e exclude

CSESLSSFI

i include

Instances
Enum CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSESiterestrictListSiteSearchFilter -> Constr #

dataTypeOf :: CSESiterestrictListSiteSearchFilter -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Hashable CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListSiteSearchFilter Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListSiteSearchFilter = D1 (MetaData "CSESiterestrictListSiteSearchFilter" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "CSESLSSFE" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSESLSSFI" PrefixI False) (U1 :: Type -> Type))

PromotionBodyLinesItem

data PromotionBodyLinesItem Source #

Instances
Eq PromotionBodyLinesItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Data PromotionBodyLinesItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: PromotionBodyLinesItem -> Constr #

dataTypeOf :: PromotionBodyLinesItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show PromotionBodyLinesItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic PromotionBodyLinesItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep PromotionBodyLinesItem :: Type -> Type #

ToJSON PromotionBodyLinesItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON PromotionBodyLinesItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep PromotionBodyLinesItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep PromotionBodyLinesItem = D1 (MetaData "PromotionBodyLinesItem" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "PromotionBodyLinesItem'" PrefixI True) ((S1 (MetaSel (Just "_pbliLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pbliURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) :*: (S1 (MetaSel (Just "_pbliHTMLTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_pbliTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

promotionBodyLinesItem :: PromotionBodyLinesItem Source #

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

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

Promotion

data Promotion Source #

Instances
Eq Promotion Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Data Promotion Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: Promotion -> Constr #

dataTypeOf :: Promotion -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Promotion Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic Promotion Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep Promotion :: Type -> Type #

ToJSON Promotion Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON Promotion Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep Promotion Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

promotion :: Promotion Source #

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

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

CSESiterestrictListLr

data CSESiterestrictListLr Source #

The language restriction for the search results

Constructors

LangAr

lang_ar Arabic

LangBg

lang_bg Bulgarian

LangCa

lang_ca Catalan

LangCs

lang_cs Czech

LangDa

lang_da Danish

LangDe

lang_de German

LangEl

lang_el Greek

LangEn

lang_en English

LangEs

lang_es Spanish

LangEt

lang_et Estonian

LangFi

lang_fi Finnish

LangFr

lang_fr French

LangHr

lang_hr Croatian

LangHu

lang_hu Hungarian

LangId

lang_id Indonesian

LangIs

lang_is Icelandic

LangIt

lang_it Italian

LangIw

lang_iw Hebrew

LangJa

lang_ja Japanese

LangKo

lang_ko Korean

LangLT

lang_lt Lithuanian

LangLv

lang_lv Latvian

LangNl

lang_nl Dutch

LangNo

lang_no Norwegian

LangPl

lang_pl Polish

LangPt

lang_pt Portuguese

LangRo

lang_ro Romanian

LangRu

lang_ru Russian

LangSk

lang_sk Slovak

LangSl

lang_sl Slovenian

LangSr

lang_sr Serbian

LangSv

lang_sv Swedish

LangTr

lang_tr Turkish

LangZhCn

lang_zh-CN Chinese (Simplified)

LangZhTw

lang_zh-TW Chinese (Traditional)

Instances
Enum CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSESiterestrictListLr -> Constr #

dataTypeOf :: CSESiterestrictListLr -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSESiterestrictListLr :: Type -> Type #

Hashable CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListLr = D1 (MetaData "CSESiterestrictListLr" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (((((C1 (MetaCons "LangAr" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangBg" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LangCa" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangCs" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "LangDa" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangDe" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LangEl" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangEn" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "LangEs" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangEt" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LangFi" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangFr" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "LangHr" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangHu" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LangId" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "LangIs" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangIt" PrefixI False) (U1 :: Type -> Type)))))) :+: ((((C1 (MetaCons "LangIw" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangJa" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LangKo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangLT" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "LangLv" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangNl" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LangNo" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "LangPl" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangPt" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "LangRo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangRu" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LangSk" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangSl" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "LangSr" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangSv" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "LangTr" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "LangZhCn" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "LangZhTw" PrefixI False) (U1 :: Type -> Type)))))))

CSESiterestrictListSearchType

data CSESiterestrictListSearchType Source #

Specifies the search type: image.

Constructors

Image

image custom image search

Instances
Enum CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSESiterestrictListSearchType -> Constr #

dataTypeOf :: CSESiterestrictListSearchType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSESiterestrictListSearchType :: Type -> Type #

Hashable CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSESiterestrictListSearchType = D1 (MetaData "CSESiterestrictListSearchType" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "Image" PrefixI False) (U1 :: Type -> Type))

Search

data Search Source #

Instances
Eq Search Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

Data Search Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: Search -> Constr #

dataTypeOf :: Search -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Search Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic Search Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep Search :: Type -> Type #

Methods

from :: Search -> Rep Search x #

to :: Rep Search x -> Search #

ToJSON Search Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON Search Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep Search Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

search :: Search Source #

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

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

CSEListLr

data CSEListLr Source #

The language restriction for the search results

Constructors

CSELLLangAr

lang_ar Arabic

CSELLLangBg

lang_bg Bulgarian

CSELLLangCa

lang_ca Catalan

CSELLLangCs

lang_cs Czech

CSELLLangDa

lang_da Danish

CSELLLangDe

lang_de German

CSELLLangEl

lang_el Greek

CSELLLangEn

lang_en English

CSELLLangEs

lang_es Spanish

CSELLLangEt

lang_et Estonian

CSELLLangFi

lang_fi Finnish

CSELLLangFr

lang_fr French

CSELLLangHr

lang_hr Croatian

CSELLLangHu

lang_hu Hungarian

CSELLLangId

lang_id Indonesian

CSELLLangIs

lang_is Icelandic

CSELLLangIt

lang_it Italian

CSELLLangIw

lang_iw Hebrew

CSELLLangJa

lang_ja Japanese

CSELLLangKo

lang_ko Korean

CSELLLangLT

lang_lt Lithuanian

CSELLLangLv

lang_lv Latvian

CSELLLangNl

lang_nl Dutch

CSELLLangNo

lang_no Norwegian

CSELLLangPl

lang_pl Polish

CSELLLangPt

lang_pt Portuguese

CSELLLangRo

lang_ro Romanian

CSELLLangRu

lang_ru Russian

CSELLLangSk

lang_sk Slovak

CSELLLangSl

lang_sl Slovenian

CSELLLangSr

lang_sr Serbian

CSELLLangSv

lang_sv Swedish

CSELLLangTr

lang_tr Turkish

CSELLLangZhCn

lang_zh-CN Chinese (Simplified)

CSELLLangZhTw

lang_zh-TW Chinese (Traditional)

Instances
Enum CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSEListLr -> Constr #

dataTypeOf :: CSEListLr -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSEListLr :: Type -> Type #

Hashable CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListLr Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListLr = D1 (MetaData "CSEListLr" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (((((C1 (MetaCons "CSELLLangAr" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangBg" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CSELLLangCa" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangCs" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CSELLLangDa" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangDe" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CSELLLangEl" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangEn" PrefixI False) (U1 :: Type -> Type)))) :+: (((C1 (MetaCons "CSELLLangEs" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangEt" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CSELLLangFi" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangFr" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CSELLLangHr" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangHu" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CSELLLangId" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSELLLangIs" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangIt" PrefixI False) (U1 :: Type -> Type)))))) :+: ((((C1 (MetaCons "CSELLLangIw" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangJa" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CSELLLangKo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangLT" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CSELLLangLv" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangNl" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CSELLLangNo" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSELLLangPl" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangPt" PrefixI False) (U1 :: Type -> Type))))) :+: (((C1 (MetaCons "CSELLLangRo" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangRu" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CSELLLangSk" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangSl" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CSELLLangSr" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangSv" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CSELLLangTr" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSELLLangZhCn" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELLLangZhTw" PrefixI False) (U1 :: Type -> Type)))))))

ContextFacetsItemItem

data ContextFacetsItemItem Source #

Instances
Eq ContextFacetsItemItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Data ContextFacetsItemItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Methods

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

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

toConstr :: ContextFacetsItemItem -> Constr #

dataTypeOf :: ContextFacetsItemItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ContextFacetsItemItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Generic ContextFacetsItemItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

Associated Types

type Rep ContextFacetsItemItem :: Type -> Type #

ToJSON ContextFacetsItemItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

FromJSON ContextFacetsItemItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep ContextFacetsItemItem Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Product

type Rep ContextFacetsItemItem = D1 (MetaData "ContextFacetsItemItem" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "ContextFacetsItemItem'" PrefixI True) (S1 (MetaSel (Just "_cfiiAnchor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: (S1 (MetaSel (Just "_cfiiLabelWithOp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)) :*: S1 (MetaSel (Just "_cfiiLabel") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

contextFacetsItemItem :: ContextFacetsItemItem Source #

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

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

CSEListSearchType

data CSEListSearchType Source #

Specifies the search type: image.

Constructors

CSELSTImage

image custom image search

Instances
Enum CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSEListSearchType -> Constr #

dataTypeOf :: CSEListSearchType -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSEListSearchType :: Type -> Type #

Hashable CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListSearchType Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListSearchType = D1 (MetaData "CSEListSearchType" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) (C1 (MetaCons "CSELSTImage" PrefixI False) (U1 :: Type -> Type))

CSEListImgSize

data CSEListImgSize Source #

Returns images of a specified size, where size can be one of: icon, small, medium, large, xlarge, xxlarge, and huge.

Constructors

CSELISHuge

huge huge

CSELISIcon

icon icon

CSELISLarge

large large

CSELISMedium

medium medium

CSELISSmall

small small

CSELISXlarge

xlarge xlarge

CSELISXxlarge

xxlarge xxlarge

Instances
Enum CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Eq CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Data CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Methods

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

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

toConstr :: CSEListImgSize -> Constr #

dataTypeOf :: CSEListImgSize -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Read CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Show CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Generic CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

Associated Types

type Rep CSEListImgSize :: Type -> Type #

Hashable CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToJSON CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromJSON CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

FromHttpApiData CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

ToHttpApiData CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListImgSize Source # 
Instance details

Defined in Network.Google.CustomSearch.Types.Sum

type Rep CSEListImgSize = D1 (MetaData "CSEListImgSize" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.4.0-AJYk0gjb9hHJ6tx06P7CTf" False) ((C1 (MetaCons "CSELISHuge" PrefixI False) (U1 :: Type -> Type) :+: (C1 (MetaCons "CSELISIcon" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELISLarge" PrefixI False) (U1 :: Type -> Type))) :+: ((C1 (MetaCons "CSELISMedium" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELISSmall" PrefixI False) (U1 :: Type -> Type)) :+: (C1 (MetaCons "CSELISXlarge" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "CSELISXxlarge" PrefixI False) (U1 :: Type -> Type))))