{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-duplicate-exports #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
{-# OPTIONS_GHC -fno-warn-unused-imports #-}
module Network.Google.Resource.Kgsearch.Entities.Search
(
EntitiesSearchResource
, entitiesSearch
, EntitiesSearch
, esXgafv
, esUploadProtocol
, esPrefix
, esAccessToken
, esUploadType
, esTypes
, esIds
, esLanguages
, esIndent
, esQuery
, esLimit
, esCallback
) where
import Network.Google.KnowledgeGraphSearch.Types
import Network.Google.Prelude
type EntitiesSearchResource =
"v1" :>
"entities:search" :>
QueryParam "$.xgafv" Xgafv :>
QueryParam "upload_protocol" Text :>
QueryParam "prefix" Bool :>
QueryParam "access_token" Text :>
QueryParam "uploadType" Text :>
QueryParams "types" Text :>
QueryParams "ids" Text :>
QueryParams "languages" Text :>
QueryParam "indent" Bool :>
QueryParam "query" Text :>
QueryParam "limit" (Textual Int32) :>
QueryParam "callback" Text :>
QueryParam "alt" AltJSON :>
Get '[JSON] SearchResponse
data EntitiesSearch = EntitiesSearch'
{ _esXgafv :: !(Maybe Xgafv)
, _esUploadProtocol :: !(Maybe Text)
, _esPrefix :: !(Maybe Bool)
, _esAccessToken :: !(Maybe Text)
, _esUploadType :: !(Maybe Text)
, _esTypes :: !(Maybe [Text])
, _esIds :: !(Maybe [Text])
, _esLanguages :: !(Maybe [Text])
, _esIndent :: !(Maybe Bool)
, _esQuery :: !(Maybe Text)
, _esLimit :: !(Maybe (Textual Int32))
, _esCallback :: !(Maybe Text)
} deriving (Eq,Show,Data,Typeable,Generic)
entitiesSearch
:: EntitiesSearch
entitiesSearch =
EntitiesSearch'
{ _esXgafv = Nothing
, _esUploadProtocol = Nothing
, _esPrefix = Nothing
, _esAccessToken = Nothing
, _esUploadType = Nothing
, _esTypes = Nothing
, _esIds = Nothing
, _esLanguages = Nothing
, _esIndent = Nothing
, _esQuery = Nothing
, _esLimit = Nothing
, _esCallback = Nothing
}
esXgafv :: Lens' EntitiesSearch (Maybe Xgafv)
esXgafv = lens _esXgafv (\ s a -> s{_esXgafv = a})
esUploadProtocol :: Lens' EntitiesSearch (Maybe Text)
esUploadProtocol
= lens _esUploadProtocol
(\ s a -> s{_esUploadProtocol = a})
esPrefix :: Lens' EntitiesSearch (Maybe Bool)
esPrefix = lens _esPrefix (\ s a -> s{_esPrefix = a})
esAccessToken :: Lens' EntitiesSearch (Maybe Text)
esAccessToken
= lens _esAccessToken
(\ s a -> s{_esAccessToken = a})
esUploadType :: Lens' EntitiesSearch (Maybe Text)
esUploadType
= lens _esUploadType (\ s a -> s{_esUploadType = a})
esTypes :: Lens' EntitiesSearch [Text]
esTypes
= lens _esTypes (\ s a -> s{_esTypes = a}) . _Default
. _Coerce
esIds :: Lens' EntitiesSearch [Text]
esIds
= lens _esIds (\ s a -> s{_esIds = a}) . _Default .
_Coerce
esLanguages :: Lens' EntitiesSearch [Text]
esLanguages
= lens _esLanguages (\ s a -> s{_esLanguages = a}) .
_Default
. _Coerce
esIndent :: Lens' EntitiesSearch (Maybe Bool)
esIndent = lens _esIndent (\ s a -> s{_esIndent = a})
esQuery :: Lens' EntitiesSearch (Maybe Text)
esQuery = lens _esQuery (\ s a -> s{_esQuery = a})
esLimit :: Lens' EntitiesSearch (Maybe Int32)
esLimit
= lens _esLimit (\ s a -> s{_esLimit = a}) .
mapping _Coerce
esCallback :: Lens' EntitiesSearch (Maybe Text)
esCallback
= lens _esCallback (\ s a -> s{_esCallback = a})
instance GoogleRequest EntitiesSearch where
type Rs EntitiesSearch = SearchResponse
type Scopes EntitiesSearch = '[]
requestClient EntitiesSearch'{..}
= go _esXgafv _esUploadProtocol _esPrefix
_esAccessToken
_esUploadType
(_esTypes ^. _Default)
(_esIds ^. _Default)
(_esLanguages ^. _Default)
_esIndent
_esQuery
_esLimit
_esCallback
(Just AltJSON)
knowledgeGraphSearchService
where go
= buildClient (Proxy :: Proxy EntitiesSearchResource)
mempty