freckle-app-1.8.0.0: Haskell application toolkit used at Freckle
Safe HaskellSafe-Inferred
LanguageHaskell2010

Freckle.App.Http.Paginate

Description

Streaming interface for paginated HTTP APIs

Examples

Take an action on each page as it is requested:

let req = parseRequest_ "https://..."

runConduit
  $ sourcePaginated httpJson req
  .| mapM_C onEachPage

onEachPage :: Response (Either HttpDecodeError [MyJsonThing]) -> m ()
onEachPage = undefined

Take and action and collect:

allPages <- runConduit
  $ sourcePaginated httpJson req
  .| iterM onEachPage
  .| sinkList

For APIs that do pagination not via Link, you can use sourcePaginatedBy

data Page a = Page
  { pData :: [a]
  , pNext :: Int
  }

instance FromJSON a => FromJSON (Item a) where
  parseJSON = withObject Page $ o -> Page
    $ o .: "data"
    * o .: "next"

runConduit
  $ sourcePaginatedBy nextPage httpJson req
  .| mapMC (fmap pData . getResponseBodyUnsafe)
  .| foldC

nextPage
  :: Request
  -> Response (Either (HttpDecodeError String) (Page a))
  -> Maybe Request
nextPage req resp = do
  body <- hush $ getResponseBody resp
  let next = C8.pack $ show $ pNext body
  pure $ addToRequestQueryString [("next", Just next)] req
Synopsis

Documentation

sourcePaginated Source #

Arguments

:: MonadIO m 
=> (Request -> m (Response body))

Run one request

-> Request

Initial request

-> ConduitT i (Response body) m () 

Stream pages of a paginated response, using Link to find next pages

sourcePaginatedBy Source #

Arguments

:: MonadIO m 
=> (Request -> Response body -> Maybe Request)

How to get the next page from each request

-> (Request -> m (Response body))

Run one request

-> Request

Initial request

-> ConduitT i (Response body) m () 

Stream pages of a paginated response, using a custom find next