[openalex] implement iso639 in it's api call

parent bf98b6c8
Pipeline #4497 failed with stages
in 9 minutes and 56 seconds
...@@ -112,6 +112,11 @@ toISO639 All = Nothing ...@@ -112,6 +112,11 @@ toISO639 All = Nothing
toISO639EN :: Lang -> ISO639.ISO639_1 toISO639EN :: Lang -> ISO639.ISO639_1
toISO639EN l = fromMaybe ISO639.EN $ toISO639 l toISO639EN l = fromMaybe ISO639.EN $ toISO639 l
iso639ToText :: ISO639.ISO639_1 -> Text
iso639ToText la = pack [a, b]
where
(a, b) = ISO639.toChars la
-- | https://en.wikipedia.org/wiki/List_of_ISO_639-1_codes -- | https://en.wikipedia.org/wiki/List_of_ISO_639-1_codes
toISO639Lang :: Lang -> Maybe Text toISO639Lang :: Lang -> Maybe Text
toISO639Lang All = Nothing toISO639Lang All = Nothing
......
...@@ -57,7 +57,7 @@ get externalAPI la q mPubmedAPIKey limit = do ...@@ -57,7 +57,7 @@ get externalAPI la q mPubmedAPIKey limit = do
Left err -> pure $ Left $ InvalidInputQuery q (T.pack err) Left err -> pure $ Left $ InvalidInputQuery q (T.pack err)
Right corpusQuery -> case externalAPI of Right corpusQuery -> case externalAPI of
OpenAlex -> first ExternalAPIError <$> OpenAlex -> first ExternalAPIError <$>
OpenAlex.get (fromMaybe "" Nothing {- email -}) q la limit OpenAlex.get (fromMaybe "" Nothing {- email -}) q (toISO639 la) limit
PubMed -> first ExternalAPIError <$> PubMed -> first ExternalAPIError <$>
PUBMED.get (fromMaybe "" mPubmedAPIKey) corpusQuery limit PUBMED.get (fromMaybe "" mPubmedAPIKey) corpusQuery limit
--docs <- PUBMED.get q default_limit -- EN only by default --docs <- PUBMED.get q default_limit -- EN only by default
......
...@@ -10,8 +10,9 @@ Portability : POSIX ...@@ -10,8 +10,9 @@ Portability : POSIX
module Gargantext.Core.Text.Corpus.API.OpenAlex where module Gargantext.Core.Text.Corpus.API.OpenAlex where
import Conduit import Conduit
import Data.LanguageCodes qualified as ISO639
import qualified Data.Text as T import qualified Data.Text as T
import Gargantext.Core (Lang, toISO639Lang) import Gargantext.Core (iso639ToText)
import Gargantext.Core.Text.Corpus.Query as Corpus import Gargantext.Core.Text.Corpus.Query as Corpus
import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..)) import Gargantext.Database.Admin.Types.Hyperdata (HyperdataDocument(..))
import Protolude import Protolude
...@@ -22,12 +23,12 @@ import Servant.Client (ClientError) ...@@ -22,12 +23,12 @@ import Servant.Client (ClientError)
get :: Text get :: Text
-> Corpus.RawQuery -> Corpus.RawQuery
-> Lang -> Maybe ISO639.ISO639_1
-> Maybe Limit -> Maybe Limit
-> IO (Either ClientError (Maybe Integer, ConduitT () HyperdataDocument IO ())) -> IO (Either ClientError (Maybe Integer, ConduitT () HyperdataDocument IO ()))
get _email q lang mLimit = do get _email q lang mLimit = do
let limit = getLimit $ fromMaybe 1000 mLimit let limit = getLimit $ fromMaybe 1000 mLimit
let mFilter = (\l -> "language:" <> l) <$> toISO639Lang lang let mFilter = (\l -> "language:" <> iso639ToText l) <$> lang
eRes <- OA.fetchWorksC Nothing mFilter $ Just $ Corpus.getRawQuery q eRes <- OA.fetchWorksC Nothing mFilter $ Just $ Corpus.getRawQuery q
pure $ (\(len, docsC) -> (len, docsC .| takeC limit .| mapC toDoc)) <$> eRes pure $ (\(len, docsC) -> (len, docsC .| takeC limit .| mapC toDoc)) <$> eRes
......
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