Commit 71413a0b authored by Mudada's avatar Mudada

Should be a good start

parent 8101e287
{-# LANGUAGE OverloadedStrings #-}
module Main where
import Lib
import SEARX
main :: IO ()
main = someFunc
main = do
res <- getMetadataWith "sociology"
case res of
(Left err) -> print err
(Right r) -> print r
name: searx
name: crawlerSEARX
version: 0.1.0.0
github: "Mudada/searx"
github: "https://git@gitlab.iscpif.fr:20022/gargantext/crawlers/searx"
license: BSD3
author: "Mudada"
maintainer: "mael.nicolas77@gmail.com"
......@@ -20,13 +20,20 @@ extra-source-files:
description: Please see the README on GitHub at <https://github.com/Mudada/searx#readme>
dependencies:
- aeson
- base >= 4.7 && < 5
- text
- lens
- servant
- servant-client
- http-client
- http-client-tls
library:
source-dirs: src
executables:
searx-exe:
crawlerSEARX-exe:
main: Main.hs
source-dirs: app
ghc-options:
......
{-# LANGUAGE OverloadedStrings #-}
module SEARX where
import Network.HTTP.Client (newManager)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import Servant.Client
import SEARX.Client
import qualified Data.Text as T
getMetadataWith :: T.Text -> IO (Either ClientError Documents)
getMetadataWith q = do
manager' <- newManager tlsManagerSettings
runClientM
(search (Just q) (Just 1) (Just 1) (Just "") (Just All) (Just Json))
(mkClientEnv manager' $ BaseUrl Https "search.iscpif.fr" 443 "")
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TemplateHaskell #-}
module SEARX.Client where
import GHC.Generics
import Data.Aeson
import Control.Applicative ((<|>))
import Servant.API
import Servant.Client
import Data.Proxy (Proxy(..))
import qualified Data.Text as T
import qualified Control.Lens as L
data Document = Document
{
_document_id :: T.Text,
_document_title :: Maybe T.Text,
_document_abstract :: Maybe T.Text,
_document_publicationDate :: Maybe T.Text,
_document_sources :: [T.Text]
} deriving (Show, Generic)
L.makeLenses ''Document
instance FromJSON Document where
parseJSON (Object o) =
Document <$>
(o .: "url")
<*> (o .:? "title")
<*> (o .:? "content")
<*> (o .:? "pubdate")
<*> (o .: "engines" <|> pure [])
data Documents = Documents
{
_documents_total :: Int,
_documents_hits :: [Document]
} deriving (Show, Generic)
L.makeLenses ''Documents
instance FromJSON Documents where
parseJSON (Object o) =
Documents <$> (o .: "number_of_results") <*> (o .: "results")
data Format = Json
deriving (Show, Generic)
instance ToHttpApiData Format where
toUrlPiece (Json) = "json"
data Language = All
deriving (Show, Generic)
instance ToHttpApiData Language where
toUrlPiece (All) = "all"
type Search =
QueryParam "q" T.Text
:> QueryParam "category_news" Int
:> QueryParam "pageno" Int
:> QueryParam "time_range" T.Text
:> QueryParam "language" Language
:> QueryParam "format" Format
:> Post '[JSON] Documents
type SEARXAPI = Search
searxProxy :: Proxy (SEARXAPI)
searxProxy = Proxy
search :: Maybe T.Text -> Maybe Int -> Maybe Int -> Maybe T.Text -> Maybe Language -> Maybe Format -> ClientM Documents
search = client searxProxy
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment