gogol-customsearch-0.2.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 # 
Eq CSEListImgType Source # 
Data CSEListImgType Source # 

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 # 
Read CSEListImgType Source # 
Show CSEListImgType Source # 
Generic CSEListImgType Source # 

Associated Types

type Rep CSEListImgType :: * -> * #

Hashable CSEListImgType Source # 
ToJSON CSEListImgType Source # 
FromJSON CSEListImgType Source # 
FromHttpApiData CSEListImgType Source # 
ToHttpApiData CSEListImgType Source # 
type Rep CSEListImgType Source # 
type Rep CSEListImgType = D1 (MetaData "CSEListImgType" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) ((:+:) ((:+:) (C1 (MetaCons "CliPart" PrefixI False) U1) (C1 (MetaCons "Face" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Lineart" PrefixI False) U1) ((:+:) (C1 (MetaCons "News" PrefixI False) U1) (C1 (MetaCons "Photo" PrefixI False) U1))))

PromotionImage

data PromotionImage Source #

Instances

Eq PromotionImage Source # 
Data PromotionImage Source # 

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 # 
Generic PromotionImage Source # 

Associated Types

type Rep PromotionImage :: * -> * #

ToJSON PromotionImage Source # 
FromJSON PromotionImage Source # 
type Rep PromotionImage Source # 
type Rep PromotionImage = D1 (MetaData "PromotionImage" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) (C1 (MetaCons "PromotionImage'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_piHeight") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) ((:*:) (S1 (MetaSel (Just Symbol "_piWidth") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_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 # 

Methods

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

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

Data Context Source # 

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 # 
Generic Context Source # 

Associated Types

type Rep Context :: * -> * #

Methods

from :: Context -> Rep Context x #

to :: Rep Context x -> Context #

ToJSON Context Source # 
FromJSON Context Source # 
type Rep Context Source # 
type Rep Context = D1 (MetaData "Context" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) (C1 (MetaCons "Context'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cFacets") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [[ContextFacetsItemItem]]))) (S1 (MetaSel (Just Symbol "_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 # 
Eq CSEListSiteSearchFilter Source # 
Data CSEListSiteSearchFilter Source # 

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 # 
Read CSEListSiteSearchFilter Source # 
Show CSEListSiteSearchFilter Source # 
Generic CSEListSiteSearchFilter Source # 
Hashable CSEListSiteSearchFilter Source # 
ToJSON CSEListSiteSearchFilter Source # 
FromJSON CSEListSiteSearchFilter Source # 
FromHttpApiData CSEListSiteSearchFilter Source # 
ToHttpApiData CSEListSiteSearchFilter Source # 
type Rep CSEListSiteSearchFilter Source # 
type Rep CSEListSiteSearchFilter = D1 (MetaData "CSEListSiteSearchFilter" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) ((:+:) (C1 (MetaCons "E" PrefixI False) U1) (C1 (MetaCons "I" PrefixI False) U1))

SearchQueries

data SearchQueries Source #

Instances

Eq SearchQueries Source # 
Data SearchQueries Source # 

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 # 
Generic SearchQueries Source # 

Associated Types

type Rep SearchQueries :: * -> * #

ToJSON SearchQueries Source # 
FromJSON SearchQueries Source # 
type Rep SearchQueries Source # 
type Rep SearchQueries = D1 (MetaData "SearchQueries" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" True) (C1 (MetaCons "SearchQueries'" PrefixI True) (S1 (MetaSel (Just Symbol "_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 # 
Data ResultPagemapAdditionalItem Source # 

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 # 
Generic ResultPagemapAdditionalItem Source # 
ToJSON ResultPagemapAdditionalItem Source # 
FromJSON ResultPagemapAdditionalItem Source # 
type Rep ResultPagemapAdditionalItem Source # 
type Rep ResultPagemapAdditionalItem = D1 (MetaData "ResultPagemapAdditionalItem" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" True) (C1 (MetaCons "ResultPagemapAdditionalItem'" PrefixI True) (S1 (MetaSel (Just Symbol "_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 # 
Data SearchURL Source # 

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 # 
Generic SearchURL Source # 

Associated Types

type Rep SearchURL :: * -> * #

ToJSON SearchURL Source # 
FromJSON SearchURL Source # 
type Rep SearchURL Source # 
type Rep SearchURL = D1 (MetaData "SearchURL" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) (C1 (MetaCons "SearchURL'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_suType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)) (S1 (MetaSel (Just Symbol "_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:

SearchSpelling

data SearchSpelling Source #

Instances

Eq SearchSpelling Source # 
Data SearchSpelling Source # 

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 # 
Generic SearchSpelling Source # 

Associated Types

type Rep SearchSpelling :: * -> * #

ToJSON SearchSpelling Source # 
FromJSON SearchSpelling Source # 
type Rep SearchSpelling Source # 
type Rep SearchSpelling = D1 (MetaData "SearchSpelling" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) (C1 (MetaCons "SearchSpelling'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_ssCorrectedQuery") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_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:

CSEListImgDominantColor

data CSEListImgDominantColor Source #

Returns images of a specific dominant color: 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

Pink

pink pink

Purple

purple purple

Teal

teal teal

White

white white

Yellow

yellow yellow

Instances

Enum CSEListImgDominantColor Source # 
Eq CSEListImgDominantColor Source # 
Data CSEListImgDominantColor Source # 

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 # 
Read CSEListImgDominantColor Source # 
Show CSEListImgDominantColor Source # 
Generic CSEListImgDominantColor Source # 
Hashable CSEListImgDominantColor Source # 
ToJSON CSEListImgDominantColor Source # 
FromJSON CSEListImgDominantColor Source # 
FromHttpApiData CSEListImgDominantColor Source # 
ToHttpApiData CSEListImgDominantColor Source # 
type Rep CSEListImgDominantColor Source # 
type Rep CSEListImgDominantColor = D1 (MetaData "CSEListImgDominantColor" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "Black" PrefixI False) U1) (C1 (MetaCons "Blue" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Brown" PrefixI False) U1) ((:+:) (C1 (MetaCons "Gray" PrefixI False) U1) (C1 (MetaCons "Green" PrefixI False) U1)))) ((:+:) ((:+:) (C1 (MetaCons "Pink" PrefixI False) U1) (C1 (MetaCons "Purple" PrefixI False) U1)) ((:+:) (C1 (MetaCons "Teal" PrefixI False) U1) ((:+:) (C1 (MetaCons "White" PrefixI False) U1) (C1 (MetaCons "Yellow" PrefixI False) U1)))))

ResultImage

data ResultImage Source #

Instances

Eq ResultImage Source # 
Data ResultImage Source # 

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 # 
Generic ResultImage Source # 

Associated Types

type Rep ResultImage :: * -> * #

ToJSON ResultImage Source # 
FromJSON ResultImage Source # 
type Rep ResultImage Source # 

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

High

high Enables highest level of safe search filtering.

Medium

medium Enables moderate safe search filtering.

Off

off Disables safe search filtering.

Instances

Enum CSEListSafe Source # 
Eq CSEListSafe Source # 
Data CSEListSafe Source # 

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 # 
Read CSEListSafe Source # 
Show CSEListSafe Source # 
Generic CSEListSafe Source # 

Associated Types

type Rep CSEListSafe :: * -> * #

Hashable CSEListSafe Source # 
ToJSON CSEListSafe Source # 
FromJSON CSEListSafe Source # 
FromHttpApiData CSEListSafe Source # 
ToHttpApiData CSEListSafe Source # 
type Rep CSEListSafe Source # 
type Rep CSEListSafe = D1 (MetaData "CSEListSafe" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) ((:+:) (C1 (MetaCons "High" PrefixI False) U1) ((:+:) (C1 (MetaCons "Medium" PrefixI False) U1) (C1 (MetaCons "Off" PrefixI False) U1)))

ResultPagemap

data ResultPagemap Source #

Instances

Eq ResultPagemap Source # 
Data ResultPagemap Source # 

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 # 
Generic ResultPagemap Source # 

Associated Types

type Rep ResultPagemap :: * -> * #

ToJSON ResultPagemap Source # 
FromJSON ResultPagemap Source # 
type Rep ResultPagemap Source # 
type Rep ResultPagemap = D1 (MetaData "ResultPagemap" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" True) (C1 (MetaCons "ResultPagemap'" PrefixI True) (S1 (MetaSel (Just Symbol "_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:

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 # 
Eq CSEListImgColorType Source # 
Data CSEListImgColorType Source # 

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 # 
Read CSEListImgColorType Source # 
Show CSEListImgColorType Source # 
Generic CSEListImgColorType Source # 
Hashable CSEListImgColorType Source # 
ToJSON CSEListImgColorType Source # 
FromJSON CSEListImgColorType Source # 
FromHttpApiData CSEListImgColorType Source # 
ToHttpApiData CSEListImgColorType Source # 
type Rep CSEListImgColorType Source # 
type Rep CSEListImgColorType = D1 (MetaData "CSEListImgColorType" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) ((:+:) (C1 (MetaCons "CSELICTColor" PrefixI False) U1) ((:+:) (C1 (MetaCons "CSELICTGray" PrefixI False) U1) (C1 (MetaCons "CSELICTMono" PrefixI False) U1)))

Result

data Result Source #

Instances

Eq Result Source # 

Methods

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

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

Data Result Source # 

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 # 
Generic Result Source # 

Associated Types

type Rep Result :: * -> * #

Methods

from :: Result -> Rep Result x #

to :: Rep Result x -> Result #

ToJSON Result Source # 
FromJSON Result Source # 
type Rep Result Source # 
type Rep Result = D1 (MetaData "Result" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) (C1 (MetaCons "Result'" PrefixI True) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rMime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rImage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ResultImage))) (S1 (MetaSel (Just Symbol "_rPagemap") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ResultPagemap))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rDisplayLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rFileFormat") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rSnippet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rKind") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rHTMLSnippet") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rHTMLFormattedURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rCacheId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rFormattedURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rHTMLTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_rLabels") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ResultLabelsItem]))) (S1 (MetaSel (Just Symbol "_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 # 
Data ResultLabelsItem Source # 

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 # 
Generic ResultLabelsItem Source # 
ToJSON ResultLabelsItem Source # 
FromJSON ResultLabelsItem Source # 
type Rep ResultLabelsItem Source # 
type Rep ResultLabelsItem = D1 (MetaData "ResultLabelsItem" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) (C1 (MetaCons "ResultLabelsItem'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rliName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rliDisplayName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_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:

SearchSearchInformation

data SearchSearchInformation Source #

Instances

Eq SearchSearchInformation Source # 
Data SearchSearchInformation Source # 

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 # 
Generic SearchSearchInformation Source # 
ToJSON SearchSearchInformation Source # 
FromJSON SearchSearchInformation Source # 
type Rep SearchSearchInformation Source # 
type Rep SearchSearchInformation = D1 (MetaData "SearchSearchInformation" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) (C1 (MetaCons "SearchSearchInformation'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_ssiSearchTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double)))) (S1 (MetaSel (Just Symbol "_ssiFormattedSearchTime") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_ssiTotalResults") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int64)))) (S1 (MetaSel (Just Symbol "_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 # 
Eq CSEListFilter Source # 
Data CSEListFilter Source # 

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 # 
Read CSEListFilter Source # 
Show CSEListFilter Source # 
Generic CSEListFilter Source # 

Associated Types

type Rep CSEListFilter :: * -> * #

Hashable CSEListFilter Source # 
ToJSON CSEListFilter Source # 
FromJSON CSEListFilter Source # 
FromHttpApiData CSEListFilter Source # 
ToHttpApiData CSEListFilter Source # 
type Rep CSEListFilter Source # 
type Rep CSEListFilter = D1 (MetaData "CSEListFilter" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) ((:+:) (C1 (MetaCons "CSELF0" PrefixI False) U1) (C1 (MetaCons "CSELF1" PrefixI False) U1))

Query

data Query Source #

Instances

Eq Query Source # 

Methods

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

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

Data Query Source # 

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 # 

Methods

showsPrec :: Int -> Query -> ShowS #

show :: Query -> String #

showList :: [Query] -> ShowS #

Generic Query Source # 

Associated Types

type Rep Query :: * -> * #

Methods

from :: Query -> Rep Query x #

to :: Rep Query x -> Query #

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

PromotionBodyLinesItem

data PromotionBodyLinesItem Source #

Instances

Eq PromotionBodyLinesItem Source # 
Data PromotionBodyLinesItem Source # 

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 # 
Generic PromotionBodyLinesItem Source # 
ToJSON PromotionBodyLinesItem Source # 
FromJSON PromotionBodyLinesItem Source # 
type Rep PromotionBodyLinesItem Source # 
type Rep PromotionBodyLinesItem = D1 (MetaData "PromotionBodyLinesItem" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) (C1 (MetaCons "PromotionBodyLinesItem'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_pbliLink") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_pbliURL") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_pbliHTMLTitle") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_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 # 
Data Promotion Source # 

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 # 
Generic Promotion Source # 

Associated Types

type Rep Promotion :: * -> * #

ToJSON Promotion Source # 
FromJSON Promotion Source # 
type Rep Promotion Source # 

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:

Search

data Search Source #

Instances

Eq Search Source # 

Methods

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

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

Data Search Source # 

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 # 
Generic Search Source # 

Associated Types

type Rep Search :: * -> * #

Methods

from :: Search -> Rep Search x #

to :: Rep Search x -> Search #

ToJSON Search Source # 
FromJSON Search Source # 
type Rep Search Source # 

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

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 CSEListLr Source # 
Eq CSEListLr Source # 
Data CSEListLr Source # 

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 # 
Read CSEListLr Source # 
Show CSEListLr Source # 
Generic CSEListLr Source # 

Associated Types

type Rep CSEListLr :: * -> * #

Hashable CSEListLr Source # 
ToJSON CSEListLr Source # 
FromJSON CSEListLr Source # 
FromHttpApiData CSEListLr Source # 
ToHttpApiData CSEListLr Source # 
type Rep CSEListLr Source # 
type Rep CSEListLr = D1 (MetaData "CSEListLr" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) ((:+:) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "LangAr" PrefixI False) U1) (C1 (MetaCons "LangBg" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LangCa" PrefixI False) U1) (C1 (MetaCons "LangCs" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "LangDa" PrefixI False) U1) (C1 (MetaCons "LangDe" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LangEl" PrefixI False) U1) (C1 (MetaCons "LangEn" PrefixI False) U1)))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "LangEs" PrefixI False) U1) (C1 (MetaCons "LangEt" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LangFi" PrefixI False) U1) (C1 (MetaCons "LangFr" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "LangHr" PrefixI False) U1) (C1 (MetaCons "LangHu" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LangId" PrefixI False) U1) ((:+:) (C1 (MetaCons "LangIs" PrefixI False) U1) (C1 (MetaCons "LangIt" PrefixI False) U1)))))) ((:+:) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "LangIw" PrefixI False) U1) (C1 (MetaCons "LangJa" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LangKo" PrefixI False) U1) (C1 (MetaCons "LangLT" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "LangLv" PrefixI False) U1) (C1 (MetaCons "LangNl" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LangNo" PrefixI False) U1) ((:+:) (C1 (MetaCons "LangPl" PrefixI False) U1) (C1 (MetaCons "LangPt" PrefixI False) U1))))) ((:+:) ((:+:) ((:+:) (C1 (MetaCons "LangRo" PrefixI False) U1) (C1 (MetaCons "LangRu" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LangSk" PrefixI False) U1) (C1 (MetaCons "LangSl" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "LangSr" PrefixI False) U1) (C1 (MetaCons "LangSv" PrefixI False) U1)) ((:+:) (C1 (MetaCons "LangTr" PrefixI False) U1) ((:+:) (C1 (MetaCons "LangZhCn" PrefixI False) U1) (C1 (MetaCons "LangZhTw" PrefixI False) U1)))))))

ContextFacetsItemItem

data ContextFacetsItemItem Source #

Instances

Eq ContextFacetsItemItem Source # 
Data ContextFacetsItemItem Source # 

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 # 
Generic ContextFacetsItemItem Source # 
ToJSON ContextFacetsItemItem Source # 
FromJSON ContextFacetsItemItem Source # 
type Rep ContextFacetsItemItem Source # 
type Rep ContextFacetsItemItem = D1 (MetaData "ContextFacetsItemItem" "Network.Google.CustomSearch.Types.Product" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) (C1 (MetaCons "ContextFacetsItemItem'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_cfiiAnchor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_cfiiLabelWithOp") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_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

Image

image custom image search

Instances

Enum CSEListSearchType Source # 
Eq CSEListSearchType Source # 
Data CSEListSearchType Source # 

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 # 
Read CSEListSearchType Source # 
Show CSEListSearchType Source # 
Generic CSEListSearchType Source # 
Hashable CSEListSearchType Source # 
ToJSON CSEListSearchType Source # 
FromJSON CSEListSearchType Source # 
FromHttpApiData CSEListSearchType Source # 
ToHttpApiData CSEListSearchType Source # 
type Rep CSEListSearchType Source # 
type Rep CSEListSearchType = D1 (MetaData "CSEListSearchType" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) (C1 (MetaCons "Image" PrefixI False) U1)

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 # 
Eq CSEListImgSize Source # 
Data CSEListImgSize Source # 

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 # 
Read CSEListImgSize Source # 
Show CSEListImgSize Source # 
Generic CSEListImgSize Source # 

Associated Types

type Rep CSEListImgSize :: * -> * #

Hashable CSEListImgSize Source # 
ToJSON CSEListImgSize Source # 
FromJSON CSEListImgSize Source # 
FromHttpApiData CSEListImgSize Source # 
ToHttpApiData CSEListImgSize Source # 
type Rep CSEListImgSize Source # 
type Rep CSEListImgSize = D1 (MetaData "CSEListImgSize" "Network.Google.CustomSearch.Types.Sum" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) ((:+:) ((:+:) (C1 (MetaCons "CSELISHuge" PrefixI False) U1) ((:+:) (C1 (MetaCons "CSELISIcon" PrefixI False) U1) (C1 (MetaCons "CSELISLarge" PrefixI False) U1))) ((:+:) ((:+:) (C1 (MetaCons "CSELISMedium" PrefixI False) U1) (C1 (MetaCons "CSELISSmall" PrefixI False) U1)) ((:+:) (C1 (MetaCons "CSELISXlarge" PrefixI False) U1) (C1 (MetaCons "CSELISXxlarge" PrefixI False) U1))))