module Data.Pagination where
import Data.Default
import Data.Maybe
import Safe
import Network.URI
import Network.URI.Params
data Pagination = Pagination
{ pnTotal :: Integer
, pnPerPage :: Integer
, pnName :: String
, pnCurrentPage :: Integer
, pnShowDesc :: Bool
} deriving (Show)
instance Default Pagination where
def = Pagination
{ pnTotal = 0
, pnPerPage = 5
, pnName = ""
, pnCurrentPage = 1
, pnShowDesc = True
}
pnPageCount :: Pagination -> Integer
pnPageCount Pagination{..} = max 1 $
if total/perpage > fromIntegral (round (total/perpage))
then round (total/perpage) + 1
else round (total/perpage)
where total = fromIntegral pnTotal
perpage = fromIntegral pnPerPage
addCurrentPage :: URI -> Pagination -> Pagination
addCurrentPage uri pagination = pagination { pnCurrentPage = currentPage } where
currentPage = fromMaybe 1 $ do
p <- lookup paramName $ uriParams uri
readMay p
paramName = pnName pagination ++ "_page"