{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedLabels #-} -- | This example program shows how to use 'Paginator's and 'Listing's, which -- are used in many API endpoints. You may notice that several of the actions -- exported by this library have a type signature similar to -- @... Paginator t a -> Listing t a@. In many cases, when you make a request to -- Reddit, it will respond with a \"view\" of the data along with controls that -- allow you to paginate through entries. This is represented as the 'Listing' -- type in @heddit@. You can use this listing to feed the next action to fetch -- more items in the form of a 'Paginator'. In addition, many of the types that -- are 'Paginable' (and thus can be used in a 'Paginator') have extra options -- that can be passed to the 'Paginator' in order to filter, limit or sort items. -- -- There are are a couple of ways to deal with 'Listing's and 'Paginator's in -- @heddit@, as the examples below aim to illustrate module Paginating where import Data.Foldable ( for_ ) import Data.Generics.Labels () import qualified Data.Text.IO as T import Lens.Micro.Platform import Network.Reddit main :: IO () main = do c <- loadClient Nothing subname <- mkSubredditName "haskell" results <- runReddit c . sequence $ [ ignorePagination, withOptions, secondPage ] <*> [ subname ] for_ (zip descs results) $ \(desc, res) -> T.putStrLn $ desc <> ": " <> getTitle res where descs = [ "1st result (without pagination)" , "1st result (all-time)" , "11th result (with pagination)" ] getTitle = maybe "No results!" (^. #title) -- | If you do not want to deal with any of this 'Listing' or 'Paginator', -- business, but would rather just get the first results that Reddit returns, -- you can use the convenience function 'firstPage' with your action. This -- ignores the pagination controls entirely, and just gets the items from the -- endpoint. You can\'t fetch subsequent items, however, or pass any additional -- options. You are thus limited to the first 100 items, with default options ignorePagination :: MonadReddit m => SubredditName -> m (Maybe Submission) ignorePagination subname = -- 'firstPage' just gets up to the first 100 items, using the default -- sort and other options firstPage (getTopSubmissions subname) <&> (^? _head) -- | This example uses a 'Paginator' to add an option telling Reddit the timeframe -- we are interested in. -- -- With actions that take a @Paginator@ and return a @Listing@, you can -- provide an initial paginator with @emptyPaginator@. @Paginator@ has -- a field @opts@ that holds an instance of the 'PaginateOptions' type -- family. Check the haddocks for the options of different 'Paginable' -- types withOptions :: MonadReddit m => SubredditName -> m (Maybe Submission) withOptions subname = do -- In this case, we specify the time range that we are interested in submissions <- getTopSubmissions subname $ emptyPaginator & #opts . #itemTime ?~ AllTime -- @submissions@ is a @Listing SubmissionID Submission@. The @children@ -- field of a listing holds the actual results. The other fields will -- be discussed below pure $ submissions ^? #children . _head -- | In this example, we can use the 'Listing' resulting from an action to get -- the next \"page\" of results secondPage :: MonadReddit m => SubredditName -> m (Maybe Submission) secondPage subname = do -- All @Paginator@s have a @limit@ field to specify the number of items -- desired, which we will set to 10 (the maximum is ostensibly 100, -- although Reddit doesn't seem to care if you exceed this; the default -- is 25) firstListing <- getTopSubmissions subname firstPaginator -- Now that we have a listing, we can turn it into a @Paginator@ to feed -- the next API call by using the function 'nextPage'. You can optionally -- provide the initial paginator as well to avoid having to set the same -- options again. -- -- All @Listing@s have @before@ and @after@ fields which act like anchors -- in the "slice" of data. They can be used as pagination controls, but are -- not necessarily present. Using @nextPage@ will create a @Paginator@ with -- corresponding @before@ and @after@ fields set to the values from the -- @Listing@. When both fields are @Just@, @after@ takes precedence. -- -- The behavior of @before@ is a little counter-intuitive (at least to me). -- It does /not/ point to data preceding the current first item in the -- @children@ field, and will only be non-null if items have been created -- that would precede it in the interim since obtaining the @Listing@. That -- is, even if you are on the nth page above 1 of the data set, @before@ will -- still be @Nothing@ unless entirely new items have been created on -- Reddit's end nextListing <- getTopSubmissions subname $ nextPage (Just firstPaginator) firstListing -- We could continue in the same vein, but we'll stop here and return the -- first child pure $ nextListing ^? #children . _head where firstPaginator = emptyPaginator & #limit .~ 10