Use fq for lang filter

Also, some refactoring for app (add debug etc).
parent 5edaca5c
......@@ -5,21 +5,24 @@ module Main where
import Conduit ( sinkList, mapM_C, (.|), runConduit )
import Data.LanguageCodes (ISO639_1(..))
import Data.Text qualified as T
import HAL (getMetadataWith, getMetadataWithC, getMetadataWithCursorC)
import HAL (getMetadataWithCursorOptsC, countResultsOpts', HalCrawlerOptions(..), defaultHalOptions)
import HAL.Doc
import HAL.Doc.Corpus (Corpus(..))
import Network.HTTP.Client (newManager)
import Network.HTTP.Client.TLS (tlsManagerSettings)
import Options.Applicative
import Prelude qualified
import Protolude
data CountParams = CountParams
{ cp_query :: [ T.Text ] }
{ cp_query :: T.Text
, cp_lang :: Maybe ISO639_1 }
data FetchParams = FetchParams
{ fp_query :: [ T.Text ]
, fp_limit :: Integer }
{ fp_query :: T.Text
, fp_limit :: Integer
, fp_lang :: Maybe ISO639_1 }
data Command =
Count CountParams
......@@ -28,13 +31,18 @@ data Command =
countParams :: Parser Command
countParams = Count <$>
(CountParams
<$> many (strArgument (metavar "query")))
<$> strArgument (metavar "query")
<*> optional (option (maybeReader readLang) (long "lang")))
fetchParams :: Parser Command
fetchParams = Fetch <$>
(FetchParams
<$> many (strArgument (metavar "query"))
<*> option auto (long "limit"))
<$> strArgument (metavar "query")
<*> option auto (long "limit")
<*> optional(option (maybeReader readLang) (long "lang")))
readLang :: Prelude.String -> Maybe ISO639_1
readLang = readMaybe
params :: Parser Command
params = subparser
......@@ -55,13 +63,15 @@ main = run =<< execParser opts
-- (Right val) -> print $ _docs val
run :: Command -> IO ()
run (Count (CountParams { cp_query })) = do
res <- getMetadataWithC cp_query (Just 0) Nothing Nothing
run (Count (CountParams { cp_query, cp_lang })) = do
res <- countResultsOpts' opts cp_query cp_lang
case res of
Left err -> putText $ show err
Right (cnt, _docsC) -> putText $ show cnt
run (Fetch (FetchParams { fp_query, fp_limit })) = do
res <- getMetadataWithCursorC fp_query (Just fp_limit) Nothing
Right cnt -> putText $ show cnt
where
opts = defaultHalOptions { _hco_debugLogs = True }
run (Fetch (FetchParams { fp_query, fp_limit, fp_lang })) = do
res <- getMetadataWithCursorOptsC opts fp_query (Just fp_limit) fp_lang
case res of
Left err -> putText $ show err
Right (_cnt, docsC) -> do
......@@ -71,6 +81,7 @@ run (Fetch (FetchParams { fp_query, fp_limit })) = do
.| sinkList
pure ()
where
opts = defaultHalOptions { _hco_debugLogs = True }
printCorpus Corpus { .. } = do
putText $ "docid: " <> _corpus_docid <> " [" <> (T.intercalate " " _corpus_title) <> "]"
putText $ " " <> (T.intercalate " " _corpus_abstract)
......
This diff is collapsed.
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