gogol-freebasesearch-0.3.0: Google Freebase Search 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.FreebaseSearch

Contents

Description

Find Freebase entities using textual queries and other constraints.

See: Freebase Search Reference

Synopsis

Service Configuration

freebaseSearchService :: ServiceConfig Source #

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

API Declaration

type FreebaseSearchAPI = ReconcileMethod :<|> SearchMethod Source #

Represents the entirety of the methods and resources available for the Freebase Search service.

Methods

freebase.reconcile

freebase.search

Types

FreebaseSearchFormat

data FreebaseSearchFormat Source #

Structural format of the json response.

Constructors

AC

ac Compact format useful for autocomplete/suggest UIs.

Classic

classic [DEPRECATED] Same format as was returned by api.freebase.com.

Entity

entity Basic information about the entities.

Guids

guids [DEPRECATED] Ordered list of a freebase guids.

Ids

ids Ordered list of freebase ids.

Mids

mids Ordered list of freebase mids.

Instances

Enum FreebaseSearchFormat Source # 
Eq FreebaseSearchFormat Source # 
Data FreebaseSearchFormat Source # 

Methods

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

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

toConstr :: FreebaseSearchFormat -> Constr #

dataTypeOf :: FreebaseSearchFormat -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FreebaseSearchFormat Source # 
Read FreebaseSearchFormat Source # 
Show FreebaseSearchFormat Source # 
Generic FreebaseSearchFormat Source # 
Hashable FreebaseSearchFormat Source # 
ToJSON FreebaseSearchFormat Source # 
FromJSON FreebaseSearchFormat Source # 
FromHttpApiData FreebaseSearchFormat Source # 
ToHttpApiData FreebaseSearchFormat Source # 
type Rep FreebaseSearchFormat Source # 
type Rep FreebaseSearchFormat = D1 (MetaData "FreebaseSearchFormat" "Network.Google.FreebaseSearch.Types.Sum" "gogol-freebasesearch-0.3.0-7HOIiRYdKQL360Ui2dvta0" False) ((:+:) ((:+:) (C1 (MetaCons "AC" PrefixI False) U1) ((:+:) (C1 (MetaCons "Classic" PrefixI False) U1) (C1 (MetaCons "Entity" PrefixI False) U1))) ((:+:) (C1 (MetaCons "Guids" PrefixI False) U1) ((:+:) (C1 (MetaCons "Ids" PrefixI False) U1) (C1 (MetaCons "Mids" PrefixI False) U1))))

ReconcileGetWarningItem

data ReconcileGetWarningItem Source #

Instances

Eq ReconcileGetWarningItem Source # 
Data ReconcileGetWarningItem Source # 

Methods

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

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

toConstr :: ReconcileGetWarningItem -> Constr #

dataTypeOf :: ReconcileGetWarningItem -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ReconcileGetWarningItem Source # 
Generic ReconcileGetWarningItem Source # 
ToJSON ReconcileGetWarningItem Source # 
FromJSON ReconcileGetWarningItem Source # 
type Rep ReconcileGetWarningItem Source # 
type Rep ReconcileGetWarningItem = D1 (MetaData "ReconcileGetWarningItem" "Network.Google.FreebaseSearch.Types.Product" "gogol-freebasesearch-0.3.0-7HOIiRYdKQL360Ui2dvta0" False) (C1 (MetaCons "ReconcileGetWarningItem'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rgwiLocation") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rgwiReason") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rgwiMessage") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))))))

reconcileGetWarningItem :: ReconcileGetWarningItem Source #

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

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

rgwiLocation :: Lens' ReconcileGetWarningItem (Maybe Text) Source #

Location of warning in the request e.g. invalid predicate.

rgwiReason :: Lens' ReconcileGetWarningItem (Maybe Text) Source #

Code for identifying classes of warnings.

rgwiMessage :: Lens' ReconcileGetWarningItem (Maybe Text) Source #

Warning message to display to the user.

FreebaseSearchScoring

data FreebaseSearchScoring Source #

Relevance scoring algorithm to use.

Constructors

FSSEntity

entity Use freebase and popularity entity ranking.

FSSFreebase

freebase Use freebase entity ranking.

FSSSchema

schema Use schema ranking for properties and types.

Instances

Enum FreebaseSearchScoring Source # 
Eq FreebaseSearchScoring Source # 
Data FreebaseSearchScoring Source # 

Methods

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

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

toConstr :: FreebaseSearchScoring -> Constr #

dataTypeOf :: FreebaseSearchScoring -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FreebaseSearchScoring Source # 
Read FreebaseSearchScoring Source # 
Show FreebaseSearchScoring Source # 
Generic FreebaseSearchScoring Source # 
Hashable FreebaseSearchScoring Source # 
ToJSON FreebaseSearchScoring Source # 
FromJSON FreebaseSearchScoring Source # 
FromHttpApiData FreebaseSearchScoring Source # 
ToHttpApiData FreebaseSearchScoring Source # 
type Rep FreebaseSearchScoring Source # 
type Rep FreebaseSearchScoring = D1 (MetaData "FreebaseSearchScoring" "Network.Google.FreebaseSearch.Types.Sum" "gogol-freebasesearch-0.3.0-7HOIiRYdKQL360Ui2dvta0" False) ((:+:) (C1 (MetaCons "FSSEntity" PrefixI False) U1) ((:+:) (C1 (MetaCons "FSSFreebase" PrefixI False) U1) (C1 (MetaCons "FSSSchema" PrefixI False) U1)))

ReconcileGetCosts

data ReconcileGetCosts Source #

Server costs for reconciling.

See: reconcileGetCosts smart constructor.

Instances

Eq ReconcileGetCosts Source # 
Data ReconcileGetCosts Source # 

Methods

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

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

toConstr :: ReconcileGetCosts -> Constr #

dataTypeOf :: ReconcileGetCosts -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ReconcileGetCosts Source # 
Generic ReconcileGetCosts Source # 
ToJSON ReconcileGetCosts Source # 
FromJSON ReconcileGetCosts Source # 
type Rep ReconcileGetCosts Source # 
type Rep ReconcileGetCosts = D1 (MetaData "ReconcileGetCosts" "Network.Google.FreebaseSearch.Types.Product" "gogol-freebasesearch-0.3.0-7HOIiRYdKQL360Ui2dvta0" False) (C1 (MetaCons "ReconcileGetCosts'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rgcHits") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32)))) (S1 (MetaSel (Just Symbol "_rgcMs") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Int32))))))

reconcileGetCosts :: ReconcileGetCosts Source #

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

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

rgcHits :: Lens' ReconcileGetCosts (Maybe Int32) Source #

Total number of hits found.

rgcMs :: Lens' ReconcileGetCosts (Maybe Int32) Source #

Total milliseconds spent.

ReconcileGet

data ReconcileGet Source #

Instances

Eq ReconcileGet Source # 
Data ReconcileGet Source # 

Methods

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

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

toConstr :: ReconcileGet -> Constr #

dataTypeOf :: ReconcileGet -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ReconcileGet Source # 
Generic ReconcileGet Source # 

Associated Types

type Rep ReconcileGet :: * -> * #

ToJSON ReconcileGet Source # 
FromJSON ReconcileGet Source # 
type Rep ReconcileGet Source # 
type Rep ReconcileGet = D1 (MetaData "ReconcileGet" "Network.Google.FreebaseSearch.Types.Product" "gogol-freebasesearch-0.3.0-7HOIiRYdKQL360Ui2dvta0" False) (C1 (MetaCons "ReconcileGet'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rgCandidate") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ReconcileCandidate]))) (S1 (MetaSel (Just Symbol "_rgCosts") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReconcileGetCosts)))) ((:*:) (S1 (MetaSel (Just Symbol "_rgWarning") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe [ReconcileGetWarningItem]))) (S1 (MetaSel (Just Symbol "_rgMatch") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReconcileCandidate))))))

reconcileGet :: ReconcileGet Source #

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

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

rgCandidate :: Lens' ReconcileGet [ReconcileCandidate] Source #

If filled, then the listed candidates are potential matches, and such should be evaluated by a more discerning algorithm or human. The matches are ordered by confidence.

rgCosts :: Lens' ReconcileGet (Maybe ReconcileGetCosts) Source #

Server costs for reconciling.

rgWarning :: Lens' ReconcileGet [ReconcileGetWarningItem] Source #

If filled, then there were recoverable problems that affected the request. For example, some of the properties were ignored because they either are not valid Freebase predicates or are not indexed for reconciliation. The candidates returned should be considered valid results, with the caveat that sections of the request were ignored as specified by the warning text.

rgMatch :: Lens' ReconcileGet (Maybe ReconcileCandidate) Source #

If filled, this entity is guaranteed to match at requested confidence probability (default 99%).

FreebaseSearchEncode

data FreebaseSearchEncode Source #

The encoding of the response. You can use this parameter to enable html encoding.

Constructors

HTML

html Encode certain characters in the response (such as tags and ambersands) using html encoding.

Off

off No encoding of the response. You should not print the results directly on an web page without html-escaping the content first.

Instances

Enum FreebaseSearchEncode Source # 
Eq FreebaseSearchEncode Source # 
Data FreebaseSearchEncode Source # 

Methods

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

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

toConstr :: FreebaseSearchEncode -> Constr #

dataTypeOf :: FreebaseSearchEncode -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FreebaseSearchEncode Source # 
Read FreebaseSearchEncode Source # 
Show FreebaseSearchEncode Source # 
Generic FreebaseSearchEncode Source # 
Hashable FreebaseSearchEncode Source # 
ToJSON FreebaseSearchEncode Source # 
FromJSON FreebaseSearchEncode Source # 
FromHttpApiData FreebaseSearchEncode Source # 
ToHttpApiData FreebaseSearchEncode Source # 
type Rep FreebaseSearchEncode Source # 
type Rep FreebaseSearchEncode = D1 (MetaData "FreebaseSearchEncode" "Network.Google.FreebaseSearch.Types.Sum" "gogol-freebasesearch-0.3.0-7HOIiRYdKQL360Ui2dvta0" False) ((:+:) (C1 (MetaCons "HTML" PrefixI False) U1) (C1 (MetaCons "Off" PrefixI False) U1))

ReconcileCandidateNotable

data ReconcileCandidateNotable Source #

Type or profession the candidate is notable for.

See: reconcileCandidateNotable smart constructor.

Instances

Eq ReconcileCandidateNotable Source # 
Data ReconcileCandidateNotable Source # 

Methods

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

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

toConstr :: ReconcileCandidateNotable -> Constr #

dataTypeOf :: ReconcileCandidateNotable -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ReconcileCandidateNotable Source # 
Generic ReconcileCandidateNotable Source # 
ToJSON ReconcileCandidateNotable Source # 
FromJSON ReconcileCandidateNotable Source # 
type Rep ReconcileCandidateNotable Source # 
type Rep ReconcileCandidateNotable = D1 (MetaData "ReconcileCandidateNotable" "Network.Google.FreebaseSearch.Types.Product" "gogol-freebasesearch-0.3.0-7HOIiRYdKQL360Ui2dvta0" False) (C1 (MetaCons "ReconcileCandidateNotable'" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_rcnName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rcnId") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))

reconcileCandidateNotable :: ReconcileCandidateNotable Source #

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

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

rcnName :: Lens' ReconcileCandidateNotable (Maybe Text) Source #

Name of notable category in specified language.

rcnId :: Lens' ReconcileCandidateNotable (Maybe Text) Source #

MID of notable category.

ReconcileCandidate

data ReconcileCandidate Source #

Instances

Eq ReconcileCandidate Source # 
Data ReconcileCandidate Source # 

Methods

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

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

toConstr :: ReconcileCandidate -> Constr #

dataTypeOf :: ReconcileCandidate -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ReconcileCandidate Source # 
Generic ReconcileCandidate Source # 
ToJSON ReconcileCandidate Source # 
FromJSON ReconcileCandidate Source # 
type Rep ReconcileCandidate Source # 
type Rep ReconcileCandidate = D1 (MetaData "ReconcileCandidate" "Network.Google.FreebaseSearch.Types.Product" "gogol-freebasesearch-0.3.0-7HOIiRYdKQL360Ui2dvta0" False) (C1 (MetaCons "ReconcileCandidate'" PrefixI True) ((:*:) ((:*:) (S1 (MetaSel (Just Symbol "_rcLang") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) (S1 (MetaSel (Just Symbol "_rcConfidence") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe (Textual Double))))) ((:*:) (S1 (MetaSel (Just Symbol "_rcName") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text))) ((:*:) (S1 (MetaSel (Just Symbol "_rcNotable") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe ReconcileCandidateNotable))) (S1 (MetaSel (Just Symbol "_rcMid") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Text)))))))

reconcileCandidate :: ReconcileCandidate Source #

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

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

rcLang :: Lens' ReconcileCandidate (Maybe Text) Source #

Language code that candidate and notable names are displayed in.

rcConfidence :: Lens' ReconcileCandidate (Maybe Double) Source #

Percentage likelihood that this candidate is the unique matching entity. Value will be between 0.0 and 1.0

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

Freebase name of matching entity in specified language.

rcNotable :: Lens' ReconcileCandidate (Maybe ReconcileCandidateNotable) Source #

Type or profession the candidate is notable for.

rcMid :: Lens' ReconcileCandidate (Maybe Text) Source #

Freebase MID of candidate entity.

FreebaseSearchHelp

data FreebaseSearchHelp Source #

The keyword to request help on.

Constructors

Langs

langs The language codes served by the service.

MAppings

mappings The property/path mappings supported by the filter and output request parameters.

Predicates

predicates The predicates and path-terminating properties supported by the filter and output request parameters.

Instances

Enum FreebaseSearchHelp Source # 
Eq FreebaseSearchHelp Source # 
Data FreebaseSearchHelp Source # 

Methods

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

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

toConstr :: FreebaseSearchHelp -> Constr #

dataTypeOf :: FreebaseSearchHelp -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FreebaseSearchHelp Source # 
Read FreebaseSearchHelp Source # 
Show FreebaseSearchHelp Source # 
Generic FreebaseSearchHelp Source # 
Hashable FreebaseSearchHelp Source # 
ToJSON FreebaseSearchHelp Source # 
FromJSON FreebaseSearchHelp Source # 
FromHttpApiData FreebaseSearchHelp Source # 
ToHttpApiData FreebaseSearchHelp Source # 
type Rep FreebaseSearchHelp Source # 
type Rep FreebaseSearchHelp = D1 (MetaData "FreebaseSearchHelp" "Network.Google.FreebaseSearch.Types.Sum" "gogol-freebasesearch-0.3.0-7HOIiRYdKQL360Ui2dvta0" False) ((:+:) (C1 (MetaCons "Langs" PrefixI False) U1) ((:+:) (C1 (MetaCons "MAppings" PrefixI False) U1) (C1 (MetaCons "Predicates" PrefixI False) U1)))

FreebaseSearchSpell

data FreebaseSearchSpell Source #

Request 'did you mean' suggestions

Constructors

Always

always Request spelling suggestions for any query at least three characters long.

NoResults

no_results Request spelling suggestions if no results were found.

NoSpelling

no_spelling Don't request spelling suggestions.

Instances

Enum FreebaseSearchSpell Source # 
Eq FreebaseSearchSpell Source # 
Data FreebaseSearchSpell Source # 

Methods

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

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

toConstr :: FreebaseSearchSpell -> Constr #

dataTypeOf :: FreebaseSearchSpell -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord FreebaseSearchSpell Source # 
Read FreebaseSearchSpell Source # 
Show FreebaseSearchSpell Source # 
Generic FreebaseSearchSpell Source # 
Hashable FreebaseSearchSpell Source # 
ToJSON FreebaseSearchSpell Source # 
FromJSON FreebaseSearchSpell Source # 
FromHttpApiData FreebaseSearchSpell Source # 
ToHttpApiData FreebaseSearchSpell Source # 
type Rep FreebaseSearchSpell Source # 
type Rep FreebaseSearchSpell = D1 (MetaData "FreebaseSearchSpell" "Network.Google.FreebaseSearch.Types.Sum" "gogol-freebasesearch-0.3.0-7HOIiRYdKQL360Ui2dvta0" False) ((:+:) (C1 (MetaCons "Always" PrefixI False) U1) ((:+:) (C1 (MetaCons "NoResults" PrefixI False) U1) (C1 (MetaCons "NoSpelling" PrefixI False) U1)))