servant-pagination-2.1.1: Type-safe pagination for Servant APIs

Safe HaskellNone
LanguageHaskell2010

Servant.Pagination

Contents

Description

Opinionated Pagination Helpers for Servant APIs

Client can provide a Range header with their request with the following format

Range: <field> [<value>][; offset <o>][; limit <l>][; order <asc|desc>]

Available ranges are declared using type-level list of accepted fields, bound to a given resource and type using the HasPagination type-class. The library provides unobtrusive types and abstract away all the plumbing to hook that on an existing Servant API.

The IsRangeType constraints summarize all constraints that must apply to a possible field and heavily rely on the FromHttpApiData and ToHttpApiData.

$ curl -v http://localhost:1337/colors -H 'Range: name; limit 10'

> GET /colors HTTP/1.1
> Host: localhost:1337
> User-Agent: curl/7.47.0
> Accept: */*
>
< HTTP/1.1 206 Partial Content
< Transfer-Encoding: chunked
< Date: Tue, 30 Jan 2018 12:45:17 GMT
< Server: Warp/3.2.13
< Content-Type: application/json;charset=utf-8
< Accept-Ranges: name
< Content-Range: name Yellow..Purple
< Next-Range: name Purple;limit 10;offset 1;order desc

The Range header is totally optional, but when provided, it indicates to the server what parts of the collection is requested. As a reponse and in addition to the data, the server may provide 3 headers to the client:

  • Accept-Ranges: A comma-separated list of field upon which a range can be defined
  • Content-Range: Actual range corresponding to the content being returned
  • Next-Range: Indicate what should be the next Range header in order to retrieve the next range

This allows the client to work in a very _dumb_ mode where it simply consumes data from the server using the value of the 'Next-Range' header to fetch each new batch of data. The 'Accept-Ranges' comes in handy to self-document the API telling the client about the available filtering and sorting options of a resource.

Here's a minimal example used to obtained the previous behavior; Most of the magic happens in the returnRange function which lift a collection of resources into a Servant handler, computing the corresponding ranges from the range used to retrieve the resources.

-- Resource Type

data Color = Color
  { name :: String
  , rgb  :: [Int]
  , hex  :: String
  } deriving (Eq, Show, Generic)

colors :: [Color]
colors = [ {- ... -} ]

-- Ranges definitions

instance HasPagination Color "name" where
  type RangeType Color "name" = String
  getFieldValue _ = name


-- API

type API =
  "colors"
    :> Header "Range" (Ranges '["name"] Color)
    :> GetPartialContent '[JSON] (Headers (PageHeaders '["name"] Color) [Color])


-- Application

defaultRange :: Range "name" String
defaultRange =
  getDefaultRange (Proxy Color)

server :: Server API
server mrange = do
  let range =
        fromMaybe defaultRange (mrange >>= extractRange)

  returnRange range (applyRange range colors)

main :: IO ()
main =
  run 1337 (serve (Proxy API) server)
Synopsis

Types

data Ranges :: [Symbol] -> * -> * Source #

A type to specify accepted Ranges via the Range HTTP Header. For example:

type API = "resources"
  :> Header "Range" (Ranges '["created_at"] Resource)
  :> Get '[JSON] [Resource]
Instances
Show (Ranges fields res) => Show (Ranges (field ': fields) res) Source # 
Instance details

Defined in Servant.Pagination

Methods

showsPrec :: Int -> Ranges (field ': fields) res -> ShowS #

show :: Ranges (field ': fields) res -> String #

showList :: [Ranges (field ': fields) res] -> ShowS #

Show (Ranges ([] :: [Symbol]) res) Source # 
Instance details

Defined in Servant.Pagination

Methods

showsPrec :: Int -> Ranges [] res -> ShowS #

show :: Ranges [] res -> String #

showList :: [Ranges [] res] -> ShowS #

ToHttpApiData (Ranges fields resource) Source # 
Instance details

Defined in Servant.Pagination

Methods

toUrlPiece :: Ranges fields resource -> Text #

toEncodedUrlPiece :: Ranges fields resource -> Builder #

toHeader :: Ranges fields resource -> ByteString #

toQueryParam :: Ranges fields resource -> Text #

(FromHttpApiData (Ranges fields resource), HasPagination resource field, KnownSymbol field, IsRangeType (RangeType resource field)) => FromHttpApiData (Ranges (field ': fields) resource) Source # 
Instance details

Defined in Servant.Pagination

Methods

parseUrlPiece :: Text -> Either Text (Ranges (field ': fields) resource) #

parseHeader :: ByteString -> Either Text (Ranges (field ': fields) resource) #

parseQueryParam :: Text -> Either Text (Ranges (field ': fields) resource) #

FromHttpApiData (Ranges ([] :: [Symbol]) resource) Source # 
Instance details

Defined in Servant.Pagination

Methods

parseUrlPiece :: Text -> Either Text (Ranges [] resource) #

parseHeader :: ByteString -> Either Text (Ranges [] resource) #

parseQueryParam :: Text -> Either Text (Ranges [] resource) #

data Range (field :: Symbol) (a :: *) Source #

An actual Range instance obtained from parsing / to generate a Range HTTP Header.

Constructors

(KnownSymbol field, IsRangeType a) => Range 

Fields

Instances
Eq (Range field a) Source # 
Instance details

Defined in Servant.Pagination

Methods

(==) :: Range field a -> Range field a -> Bool #

(/=) :: Range field a -> Range field a -> Bool #

Show (Range field a) Source # 
Instance details

Defined in Servant.Pagination

Methods

showsPrec :: Int -> Range field a -> ShowS #

show :: Range field a -> String #

showList :: [Range field a] -> ShowS #

data RangeOrder Source #

Define the sorting order of the paginated resources (ascending or descending)

Constructors

RangeAsc 
RangeDesc 
Instances
Eq RangeOrder Source # 
Instance details

Defined in Servant.Pagination

Ord RangeOrder Source # 
Instance details

Defined in Servant.Pagination

Show RangeOrder Source # 
Instance details

Defined in Servant.Pagination

Generic RangeOrder Source # 
Instance details

Defined in Servant.Pagination

Associated Types

type Rep RangeOrder :: * -> * #

ToHttpApiData RangeOrder Source # 
Instance details

Defined in Servant.Pagination

FromHttpApiData RangeOrder Source # 
Instance details

Defined in Servant.Pagination

type Rep RangeOrder Source # 
Instance details

Defined in Servant.Pagination

type Rep RangeOrder = D1 (MetaData "RangeOrder" "Servant.Pagination" "servant-pagination-2.1.1-5zDC7SAqTEz5IwAg7wXo9A" False) (C1 (MetaCons "RangeAsc" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "RangeDesc" PrefixI False) (U1 :: * -> *))

data AcceptRanges (fields :: [Symbol]) Source #

Accepted Ranges in the `Accept-Ranges` response's header

Constructors

AcceptRanges 
Instances
(ToHttpApiData (AcceptRanges (f ': fs)), KnownSymbol field) => ToHttpApiData (AcceptRanges (field ': (f ': fs))) Source # 
Instance details

Defined in Servant.Pagination

Methods

toUrlPiece :: AcceptRanges (field ': (f ': fs)) -> Text #

toEncodedUrlPiece :: AcceptRanges (field ': (f ': fs)) -> Builder #

toHeader :: AcceptRanges (field ': (f ': fs)) -> ByteString #

toQueryParam :: AcceptRanges (field ': (f ': fs)) -> Text #

KnownSymbol field => ToHttpApiData (AcceptRanges (field ': ([] :: [Symbol]))) Source # 
Instance details

Defined in Servant.Pagination

Methods

toUrlPiece :: AcceptRanges (field ': []) -> Text #

toEncodedUrlPiece :: AcceptRanges (field ': []) -> Builder #

toHeader :: AcceptRanges (field ': []) -> ByteString #

toQueryParam :: AcceptRanges (field ': []) -> Text #

data ContentRange (fields :: [Symbol]) resource Source #

Actual range returned, in the `Content-Range` response's header

Constructors

(KnownSymbol field, ToHttpApiData (RangeType resource field)) => ContentRange 

Fields

Instances
ToHttpApiData (ContentRange fields res) Source # 
Instance details

Defined in Servant.Pagination

Methods

toUrlPiece :: ContentRange fields res -> Text #

toEncodedUrlPiece :: ContentRange fields res -> Builder #

toHeader :: ContentRange fields res -> ByteString #

toQueryParam :: ContentRange fields res -> Text #

type PageHeaders (fields :: [Symbol]) (resource :: *) = '[Header "Accept-Ranges" (AcceptRanges fields), Header "Content-Range" (ContentRange fields resource), Header "Next-Range" (Ranges fields resource)] Source #

Type alias to declare response headers related to pagination

type MyHeaders =
  PageHeaders '["created_at"] Resource

type API = "resources"
  :> Header "Range" (Ranges '["created_at"] Resource)
  :> Get '[JSON] (Headers MyHeaders [Resource])

type IsRangeType a = (Show a, Ord a, Eq a, FromHttpApiData a, ToHttpApiData a) Source #

Set of constraints that must apply to every type target of a Range

Declare Ranges

class KnownSymbol field => HasPagination resource field where Source #

Available Range on a given resource must implements the HasPagination type-class. This class defines how the library can interact with a given resource to access the value to which a field refers.

Minimal complete definition

getFieldValue

Associated Types

type RangeType resource field :: * Source #

Methods

getFieldValue :: Proxy field -> resource -> RangeType resource field Source #

Get the corressponding value of a Resource

getRangeOptions :: Proxy field -> Proxy resource -> RangeOptions Source #

Get parsing options for the Range defined on this field

getDefaultRange :: IsRangeType (RangeType resource field) => Proxy resource -> Range field (RangeType resource field) Source #

Create a default Range from a value and default RangeOptions. Typical use-case is for when no or an invalid Range header was provided.

data RangeOptions Source #

Default values to apply when parsing a Range

Constructors

RangeOptions 

Fields

Instances
Eq RangeOptions Source # 
Instance details

Defined in Servant.Pagination

Show RangeOptions Source # 
Instance details

Defined in Servant.Pagination

defaultOptions :: RangeOptions Source #

Some default options of default values for a Range (limit 100; offset 0; order desc)

Use Ranges

extractRange Source #

Arguments

:: (ExtractRange fields field, HasPagination resource field) 
=> Ranges fields resource

A list of accepted Ranges for the API

-> Maybe (Range field (RangeType resource field))

A Range instance of the expected type, if it matches

Extract a Range from a Ranges. Works like a safe read, trying to coerce a Range instance to an expected type. Type annotation are most likely necessary to remove ambiguity. Note that a Range can only be extracted to a type bound by the allowed fields on a given resource.

extractDateRange :: Ranges '["created_at", "name"] Resource -> Range "created_at" UTCTime
extractDateRange =
  extractRange

putRange :: (PutRange fields field, HasPagination resource field) => Range field (RangeType resource field) -> Ranges fields resource Source #

returnRange Source #

Arguments

:: (Monad m, ToHttpApiData (AcceptRanges fields), KnownSymbol field, HasPagination resource field, IsRangeType (RangeType resource field), PutRange fields field) 
=> Range field (RangeType resource field)

Actual Range used to retrieve the results

-> [resource]

Resources to return, fetched from a db or a local store

-> m (Headers (PageHeaders fields resource) [resource])

Resources embedded in a given Monad (typically a Handler, with pagination headers)

Lift an API response in a Monad, typically a Handler. Ranges headers can be quite cumbersome to declare and can be deduced from the resources returned and the previous Range. This is exactly what this function does.

myHandler
 :: Maybe (Ranges '["created_at"] Resource)
 -> Handler (Headers (PageHeaders '["created_at"] Resource) [Resource])
myHandler mrange =
 let range =
       fromMaybe (getDefaultRange (Proxy @Resource)) (mrange >>= extractRange)

 returnRange range (applyRange range resources)

applyRange Source #

Arguments

:: HasPagination resource field 
=> Range field (RangeType resource field)

A Range instance on a given resource

-> [resource]

A full-list of resource

-> [resource]

The sublist obtained by applying the Range

Helper to apply a Range to a list of values. Most likely useless in practice as results may come more realistically from a database, but useful for debugging or testing.