module IHP.Pagination.ViewFunctions ( module IHP.Pagination.Types, renderPagination, renderFilter, ) where import IHP.Prelude import IHP.Pagination.Types import IHP.Pagination.Helpers import IHP.ControllerSupport import Text.Blaze.Html (Html) import IHP.HSX.QQ (hsx) import IHP.Controller.Param (paramOrNothing) import qualified Network.Wai as Wai import qualified Network.HTTP.Types.URI as Query import IHP.ViewSupport (theRequest, theCSSFramework) import qualified Data.Containers.ListUtils as List import IHP.View.Types (PaginationView(..), styledPagination, styledPaginationPageLink, styledPaginationDotDot, styledPaginationItemsPerPageSelector, styledPaginationLinkPrevious, styledPaginationLinkNext) -- | Render a navigation for your pagination. This is to be used in your view whenever -- to allow users to change pages, including "Next" and "Previous". -- If there is only one page, this will not render anything. renderPagination :: (?context::ControllerContext) => Pagination -> Html renderPagination pagination@Pagination {currentPage, window, pageSize} = when (showPagination pagination) $ styledPagination theCSSFramework theCSSFramework paginationView where paginationView = PaginationView { cssFramework = theCSSFramework , pagination = pagination , pageUrl = pageUrl , linkPrevious = linkPrevious , linkNext = linkNext , pageDotDotItems = pageDotDotItems , itemsPerPageSelector = itemsPerPageSelector } linkPrevious = styledPaginationLinkPrevious theCSSFramework theCSSFramework pagination (pageUrl $ currentPage - 1) linkNext = styledPaginationLinkNext theCSSFramework theCSSFramework pagination (pageUrl $ currentPage + 1) itemsPerPageSelector = styledPaginationItemsPerPageSelector theCSSFramework theCSSFramework pagination itemsPerPageUrl pageDotDotItems = [hsx|{forEach (processedPages pages) pageDotDotItem}|] pageDotDotItem pg = case pg of Page n -> styledPaginationPageLink theCSSFramework theCSSFramework pagination (pageUrl n) n DotDot n -> styledPaginationDotDot theCSSFramework theCSSFramework pagination pageUrl n = path <> Query.renderQuery True newQueryString where -- "?page=" ++ show n ++ maybeFilter ++ maybeMaxItems path = Wai.rawPathInfo theRequest queryString = Wai.queryString theRequest newQueryString = queryString |> setQueryValue "page" (cs $ show n) |> maybeFilter |> maybeMaxItems itemsPerPageUrl n = path <> Query.renderQuery True newQueryString where path = Wai.rawPathInfo theRequest queryString = Wai.queryString theRequest newQueryString = queryString |> setQueryValue "maxItems" (cs $ tshow n) -- If we change the number of items, we should jump back to the first page -- so we are not out of the items bound. |> setQueryValue "page" (cs $ show 1) maybeFilter queryString = case paramOrNothing @Text "filter" of Nothing -> queryString Just "" -> queryString Just filterValue -> queryString |> setQueryValue "filter" (cs filterValue) maybeMaxItems queryString = case paramOrNothing @Int "maxItems" of Nothing -> queryString Just m -> queryString |> setQueryValue "maxItems" (cs $ tshow m) processedPages (pg0:pg1:rest) = if pg1 == pg0 + 1 then Page pg0 : processedPages (pg1:rest) else Page pg0 : DotDot ((pg1+pg0) `div` 2) : processedPages (pg1:rest) processedPages [pg] = [Page pg] processedPages [] = [] pages = let totalPages = getLastPage pagination lowerBound | currentPage - window < 1 = 1 | currentPage + window > totalPages = totalPages - window * 2 + 1 | otherwise = currentPage - window upperBound | currentPage + window > totalPages = totalPages | currentPage - window < 1 = window * 2 | otherwise = currentPage + window in if window > totalPages then [1..getLastPage pagination] else List.nubInt $ 1 : [max 1 lowerBound..min (getLastPage pagination) upperBound] ++ [totalPages] -- | Render a filtering box in your view. Allows the user to type in a query and filter -- results according to what they type. -- -- Below is an example of how this might be used in your index. Replace the existing