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.Resource.Search.CSE.List

Contents

Description

Returns metadata about the search performed, metadata about the custom search engine used for the search, and the search results.

See: CustomSearch API Reference for search.cse.list.

Synopsis

REST Resource

type CSEListResource = "customsearch" :> ("v1" :> (QueryParam "q" Text :> (QueryParam "imgDominantColor" CSEListImgDominantColor :> (QueryParam "siteSearchFilter" CSEListSiteSearchFilter :> (QueryParam "c2coff" Text :> (QueryParam "orTerms" Text :> (QueryParam "start" (Textual Word32) :> (QueryParam "rights" Text :> (QueryParam "excludeTerms" Text :> (QueryParam "num" (Textual Word32) :> (QueryParam "fileType" Text :> (QueryParam "searchType" CSEListSearchType :> (QueryParam "lr" CSEListLr :> (QueryParam "googlehost" Text :> (QueryParam "relatedSite" Text :> (QueryParam "hl" Text :> (QueryParam "cref" Text :> (QueryParam "sort" Text :> (QueryParam "siteSearch" Text :> (QueryParam "filter" CSEListFilter :> (QueryParam "dateRestrict" Text :> (QueryParam "linkSite" Text :> (QueryParam "lowRange" Text :> (QueryParam "imgType" CSEListImgType :> (QueryParam "gl" Text :> (QueryParam "cx" Text :> (QueryParam "imgColorType" CSEListImgColorType :> (QueryParam "imgSize" CSEListImgSize :> (QueryParam "exactTerms" Text :> (QueryParam "cr" Text :> (QueryParam "safe" CSEListSafe :> (QueryParam "hq" Text :> (QueryParam "highRange" Text :> (QueryParam "alt" AltJSON :> Get '[JSON] Search)))))))))))))))))))))))))))))))))) Source #

A resource alias for search.cse.list method which the CSEList request conforms to.

Creating a Request

data CSEList Source #

Returns metadata about the search performed, metadata about the custom search engine used for the search, and the search results.

See: cSEList smart constructor.

Instances

Eq CSEList Source # 

Methods

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

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

Data CSEList Source # 

Methods

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

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

toConstr :: CSEList -> Constr #

dataTypeOf :: CSEList -> DataType #

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

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

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

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

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

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

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

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

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

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

Show CSEList Source # 
Generic CSEList Source # 

Associated Types

type Rep CSEList :: * -> * #

Methods

from :: CSEList -> Rep CSEList x #

to :: Rep CSEList x -> CSEList #

GoogleRequest CSEList Source # 

Associated Types

type Rs CSEList :: * #

type Scopes CSEList :: [Symbol] #

type Rep CSEList Source # 
type Rep CSEList = D1 (MetaData "CSEList" "Network.Google.Resource.Search.CSE.List" "gogol-customsearch-0.2.0-3I4pTN2CJTJ4odwCUjYi0G" False) (C1 (MetaCons "CSEList'" PrefixI True) ((:*:) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cselImgDominantColor") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CSEListImgDominantColor))) (S1 (MetaSel (Just Symbol "_cselSiteSearchFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CSEListSiteSearchFilter)))) ((:*:) (S1 (MetaSel (Just Symbol "_cselC2coff") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cselOrTerms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cselStart") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Word32)))) (S1 (MetaSel (Just Symbol "_cselRights") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cselExcludeTerms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cselNum") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Textual Word32)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cselFileType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cselSearchType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CSEListSearchType)))) ((:*:) (S1 (MetaSel (Just Symbol "_cselLr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CSEListLr))) (S1 (MetaSel (Just Symbol "_cselQ") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 Text)))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cselGooglehost") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cselRelatedSite") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cselHl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cselCref") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))) ((:*:) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cselSort") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cselSiteSearch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cselFilter") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CSEListFilter))) (S1 (MetaSel (Just Symbol "_cselDateRestrict") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cselLinkSite") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cselLowRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))) ((:*:) (S1 (MetaSel (Just Symbol "_cselImgType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CSEListImgType))) (S1 (MetaSel (Just Symbol "_cselGl") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))) ((:*:) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cselCx") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cselImgColorType") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CSEListImgColorType)))) ((:*:) (S1 (MetaSel (Just Symbol "_cselImgSize") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe CSEListImgSize))) (S1 (MetaSel (Just Symbol "_cselExactTerms") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_cselCr") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cselSafe") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 CSEListSafe))) ((:*:) (S1 (MetaSel (Just Symbol "_cselHq") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_cselHighRange") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))))
type Scopes CSEList Source # 
type Rs CSEList Source # 

Request Lenses

cselImgDominantColor :: Lens' CSEList (Maybe CSEListImgDominantColor) Source #

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

cselSiteSearchFilter :: Lens' CSEList (Maybe CSEListSiteSearchFilter) Source #

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

cselC2coff :: Lens' CSEList (Maybe Text) Source #

Turns off the translation between zh-CN and zh-TW.

cselOrTerms :: Lens' CSEList (Maybe Text) Source #

Provides additional search terms to check for in a document, where each document in the search results must contain at least one of the additional search terms

cselStart :: Lens' CSEList (Maybe Word32) Source #

The index of the first result to return

cselRights :: Lens' CSEList (Maybe Text) Source #

Filters based on licensing. Supported values include: cc_publicdomain, cc_attribute, cc_sharealike, cc_noncommercial, cc_nonderived and combinations of these.

cselExcludeTerms :: Lens' CSEList (Maybe Text) Source #

Identifies a word or phrase that should not appear in any documents in the search results

cselNum :: Lens' CSEList Word32 Source #

Number of search results to return

cselFileType :: Lens' CSEList (Maybe Text) Source #

Returns images of a specified type. Some of the allowed values are: bmp, gif, png, jpg, svg, pdf, ...

cselSearchType :: Lens' CSEList (Maybe CSEListSearchType) Source #

Specifies the search type: image.

cselLr :: Lens' CSEList (Maybe CSEListLr) Source #

The language restriction for the search results

cselGooglehost :: Lens' CSEList (Maybe Text) Source #

The local Google domain to use to perform the search.

cselRelatedSite :: Lens' CSEList (Maybe Text) Source #

Specifies that all search results should be pages that are related to the specified URL

cselHl :: Lens' CSEList (Maybe Text) Source #

Sets the user interface language.

cselCref :: Lens' CSEList (Maybe Text) Source #

The URL of a linked custom search engine

cselSort :: Lens' CSEList (Maybe Text) Source #

The sort expression to apply to the results

cselSiteSearch :: Lens' CSEList (Maybe Text) Source #

Specifies all search results should be pages from a given site

cselFilter :: Lens' CSEList (Maybe CSEListFilter) Source #

Controls turning on or off the duplicate content filter.

cselDateRestrict :: Lens' CSEList (Maybe Text) Source #

Specifies all search results are from a time period

cselLinkSite :: Lens' CSEList (Maybe Text) Source #

Specifies that all search results should contain a link to a particular URL

cselLowRange :: Lens' CSEList (Maybe Text) Source #

Creates a range in form as_nlo value..as_nhi value and attempts to append it to query

cselImgType :: Lens' CSEList (Maybe CSEListImgType) Source #

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

cselGl :: Lens' CSEList (Maybe Text) Source #

Geolocation of end user.

cselCx :: Lens' CSEList (Maybe Text) Source #

The custom search engine ID to scope this search query

cselImgColorType :: Lens' CSEList (Maybe CSEListImgColorType) Source #

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

cselImgSize :: Lens' CSEList (Maybe CSEListImgSize) Source #

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

cselExactTerms :: Lens' CSEList (Maybe Text) Source #

Identifies a phrase that all documents in the search results must contain

cselCr :: Lens' CSEList (Maybe Text) Source #

Country restrict(s).

cselSafe :: Lens' CSEList CSEListSafe Source #

Search safety level

cselHq :: Lens' CSEList (Maybe Text) Source #

Appends the extra query terms to the query.

cselHighRange :: Lens' CSEList (Maybe Text) Source #

Creates a range in form as_nlo value..as_nhi value and attempts to append it to query