Commit 0b906ccc authored by Alexandre Delanoë's avatar Alexandre Delanoë

[FIX] Adding a threadelay to not be banned

parent 02e03d9b
...@@ -2,6 +2,7 @@ module PUBMED where ...@@ -2,6 +2,7 @@ module PUBMED where
import Conduit import Conduit
import Control.Applicative import Control.Applicative
import Control.Concurrent (threadDelay)
import Data.Attoparsec.ByteString import Data.Attoparsec.ByteString
import Data.Attoparsec.ByteString.Char8 (anyChar) import Data.Attoparsec.ByteString.Char8 (anyChar)
import Data.ByteString.Char8 (pack) import Data.ByteString.Char8 (pack)
...@@ -10,9 +11,9 @@ import Data.Maybe (fromMaybe) ...@@ -10,9 +11,9 @@ import Data.Maybe (fromMaybe)
import Data.Text (Text) import Data.Text (Text)
import Network.HTTP.Client (newManager) import Network.HTTP.Client (newManager)
import Network.HTTP.Client.TLS (tlsManagerSettings) import Network.HTTP.Client.TLS (tlsManagerSettings)
import Panic (panic)
import PUBMED.Client import PUBMED.Client
import PUBMED.Parser import PUBMED.Parser
import Panic (panic)
import Prelude hiding (takeWhile) import Prelude hiding (takeWhile)
import Servant.Client (runClientM, mkClientEnv, BaseUrl(..), ClientEnv, ClientError, Scheme(..)) import Servant.Client (runClientM, mkClientEnv, BaseUrl(..), ClientEnv, ClientError, Scheme(..))
import qualified Data.ByteString.Lazy as LBS import qualified Data.ByteString.Lazy as LBS
...@@ -61,9 +62,11 @@ getPage :: ClientEnv -> Text -> Int -> Int -> IO [PubMed] ...@@ -61,9 +62,11 @@ getPage :: ClientEnv -> Text -> Int -> Int -> IO [PubMed]
getPage env q perPage pageNum = do getPage env q perPage pageNum = do
let offset = fromIntegral $ pageNum * perPage let offset = fromIntegral $ pageNum * perPage
eDocs <- runSimpleFindPubmedAbstractRequest q (Just offset) (Just $ fromIntegral perPage) eDocs <- runSimpleFindPubmedAbstractRequest q (Just offset) (Just $ fromIntegral perPage)
pure $ case eDocs of case eDocs of
Left err -> panic $ "[getPage] error: " <> show err Left err -> panic $ "[getPage] error: " <> show err
Right docs -> docs Right docs -> do
_ <- threadDelay 1000000 -- One seconds
pure docs
-- | TODO this parser need at least one subs at the end -- | TODO this parser need at least one subs at the end
-- (use endOfInput) -- (use endOfInput)
......
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