persistent-pagination-0.1.1.2: Efficient and correct pagination for persistent or esqueleto queries.
Safe HaskellNone
LanguageHaskell2010

Database.Persist.Pagination.Types

Synopsis

Documentation

newtype PageSize Source #

The amount of records in a Page of results.

Since: 0.1.0.0

Constructors

PageSize 

Fields

Instances

Instances details
Eq PageSize Source # 
Instance details

Defined in Database.Persist.Pagination.Types

Show PageSize Source # 
Instance details

Defined in Database.Persist.Pagination.Types

data SortOrder Source #

Whether to sort by ASC or DESC when you're paging over results.

Since: 0.1.0.0

Constructors

Ascend 
Descend 

Instances

Instances details
Eq SortOrder Source # 
Instance details

Defined in Database.Persist.Pagination.Types

Show SortOrder Source # 
Instance details

Defined in Database.Persist.Pagination.Types

data Range t Source #

A datatype describing the min and max value of the relevant field that you are ranging over in a non-empty sequence of records.

Since: 0.1.0.0

Constructors

Range 

Fields

Instances

Instances details
Functor Range Source # 
Instance details

Defined in Database.Persist.Pagination.Types

Methods

fmap :: (a -> b) -> Range a -> Range b #

(<$) :: a -> Range b -> Range a #

Foldable Range Source # 
Instance details

Defined in Database.Persist.Pagination.Types

Methods

fold :: Monoid m => Range m -> m #

foldMap :: Monoid m => (a -> m) -> Range a -> m #

foldMap' :: Monoid m => (a -> m) -> Range a -> m #

foldr :: (a -> b -> b) -> b -> Range a -> b #

foldr' :: (a -> b -> b) -> b -> Range a -> b #

foldl :: (b -> a -> b) -> b -> Range a -> b #

foldl' :: (b -> a -> b) -> b -> Range a -> b #

foldr1 :: (a -> a -> a) -> Range a -> a #

foldl1 :: (a -> a -> a) -> Range a -> a #

toList :: Range a -> [a] #

null :: Range a -> Bool #

length :: Range a -> Int #

elem :: Eq a => a -> Range a -> Bool #

maximum :: Ord a => Range a -> a #

minimum :: Ord a => Range a -> a #

sum :: Num a => Range a -> a #

product :: Num a => Range a -> a #

Traversable Range Source # 
Instance details

Defined in Database.Persist.Pagination.Types

Methods

traverse :: Applicative f => (a -> f b) -> Range a -> f (Range b) #

sequenceA :: Applicative f => Range (f a) -> f (Range a) #

mapM :: Monad m => (a -> m b) -> Range a -> m (Range b) #

sequence :: Monad m => Range (m a) -> m (Range a) #

Eq t => Eq (Range t) Source # 
Instance details

Defined in Database.Persist.Pagination.Types

Methods

(==) :: Range t -> Range t -> Bool #

(/=) :: Range t -> Range t -> Bool #

Show t => Show (Range t) Source # 
Instance details

Defined in Database.Persist.Pagination.Types

Methods

showsPrec :: Int -> Range t -> ShowS #

show :: Range t -> String #

showList :: [Range t] -> ShowS #

Ord t => Semigroup (Range t) Source # 
Instance details

Defined in Database.Persist.Pagination.Types

Methods

(<>) :: Range t -> Range t -> Range t #

sconcat :: NonEmpty (Range t) -> Range t #

stimes :: Integral b => b -> Range t -> Range t #

(Bounded t, Ord t) => Monoid (Range t) Source # 
Instance details

Defined in Database.Persist.Pagination.Types

Methods

mempty :: Range t #

mappend :: Range t -> Range t -> Range t #

mconcat :: [Range t] -> Range t #

type DesiredRange t = Range (Maybe t) Source #

Users aren't required to put a value in for the range - a value of Nothing is equivalent to saying "unbounded from below."

Since: 0.1.0.0

bumpPageRange :: Ord typ => SortOrder -> DesiredRange typ -> Range typ -> DesiredRange typ Source #

Modify the DesiredRange according to the Range that was provided by the query and the SortOrder.

Since: 0.1.0.0