{-# LANGUAGE TransformListComp #-} module GalleryPage (make) where import Control.Exception import Data.Function (on, (&)) import Data.List (sortOn, groupBy) import qualified Data.Text.Lazy as Lazy import System.FilePath ((), takeDirectory, joinPath, splitPath) import GHC.Exts (Down (..), the) import BuilderQQ import Depend (thumbFile) import Info newtype NoThumb = NoThumb FilePath deriving stock Eq deriving anyclass Exception instance Show NoThumb where show (NoThumb dir) = "no thumbnail for " ++ dir make :: Text -- ^ title -> FilePath -- ^ gallery url prefix -> Bool -- ^ nsfw is included? -> [(FilePath, Info)] -> Lazy.Text make title prefix nsfw infos = toLazyText $ make' title prefix nsfw infos make' :: Text -> FilePath -> Bool -> [(FilePath, Info)] -> Builder make' title prefix nsfw infos = [b|@0 $*title

$*title

rss

|] where items = map (uncurry $ makeYearItems nsfw) infosByYear infosByYear = [(the year, infopath) | infopath@(_, info) <- infos, then sortOn by Down info, let year = #year info, then group by Down year using groupBy'] groupBy' f = groupBy ((==) `on` f) undir = joinPath (replicate (length (splitPath prefix)) "..") makeYearItems :: Bool -- ^ nsfw -> Integer -- ^ year -> [(FilePath, Info)] -> Builder makeYearItems nsfw year infos = [b|@4
  • $year' $4.items |] where items = map (uncurry $ makeItem nsfw) infos year' = show year & foldMap \c -> [b|$'c|] makeItem :: Bool -> FilePath -> Info -> Builder makeItem nsfw file info@(Info {title}) = [b|@4
  • $*title
    |] where dir = takeDirectory file thumb = maybe (throw $ NoThumb dir) (\t -> dir thumbFile t) $ #thumb info nsfw' = if nsfw && #anyNsfw info then " nsfw" else ""