I have the following code which grabs two pages of data from a paginated API endpoint. I'd like to modify query
function to keep getting pages until it finds no more data (so replace take 2
in the code below with something which looks at the API response).
My question is wether it is possible to achieve this without changing query
function to an IO
function. And if so, how would I go about it. If not, is there a way of doing this without writing recursive function?
Here is the code:
#!/usr/bin/env stack
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeOperators #-}
import Servant.Client
import Network.HTTP.Client (newManager, defaultManagerSettings)
import Data.Proxy
import Servant.API
import Data.Aeson
import GHC.Generics
-- data type
data BlogPost = BlogPost
{ id :: Integer
, title :: String
} deriving (Show, Generic)
instance FromJSON BlogPost
-- api client
type API = "posts" :> QueryParam "_page" Integer :> Get '[JSON] [BlogPost]
api :: Proxy API
api = Proxy
posts :: Maybe Integer -> ClientM [BlogPost]
posts = client api
-- query by page
query :: ClientM [[BlogPost]]
query = sequence $ take 2 $ map posts pages
where
pages = [Just p | p <- [1..]]
-- main
main :: IO ()
main = do
manager' <- newManager defaultManagerSettings
let url = ClientEnv manager' (BaseUrl Http "jsonplaceholder.typicode.com" 80 "")
posts' <- runClientM query url
print posts'
I've tried to use takeWhileM
to do this and ended up making query an IO
function and passing url
into it. It was starting to look pretty horrible and I couldn't get the types to match up (I felt like I needed something more like (a -> m Bool) -> m [a] -> m [a]
rather than (a -> m Bool) -> [a] -> m [a]
which is what takeWhileM
is - still find this strange because I see this function as a filter, yet the input list and output list are different (one has monad around it and the other doesn't)).