{-# LANGUAGE PatternSynonyms #-}
module SinglePage (make) where
import Date
import Info
import BuilderQQ
import qualified NsfwWarning
import Control.Exception
import Control.Monad
import Data.List (sort, intersperse)
import Data.Maybe (fromMaybe, isNothing, isJust)
import qualified Data.Text as Strict
import qualified Data.Text.Lazy as Lazy
import System.FilePath (joinPath, splitPath)
import qualified Data.HashSet as Set
import Data.Traversable
import Data.Semigroup
import Data.List.NonEmpty (toList)
-- | e.g. only nsfw images are present for a non-nsfw page
newtype NoEligibleImages = NoEligibleImages {title :: Strict.Text}
deriving stock Eq deriving anyclass Exception
instance Show NoEligibleImages where
show (NoEligibleImages {title}) =
Strict.unpack title <> ": no images selected\n" <>
" (probably a nsfw-only work without --nsfw set)"
make :: Text -- ^ website root
-> Text -- ^ website name
-> FilePath -- ^ gallery prefix
-> Bool -- ^ nsfw?
-> FilePath -- ^ data dir
-> FilePath -- ^ subdir of datadir containing this @info.yaml@
-> Info -> IO Lazy.Text
make root siteName prefix nsfw dataDir dir info =
toLazyText <$> make' root siteName prefix nsfw dataDir dir info
make' :: Text -> Text -> FilePath -> Bool -> FilePath -> FilePath -> Info
-> IO Builder
make' root siteName prefix nsfw _dataDir dir
info@(Info {date, title, artist, bg}) = do
images <- maybe (throw $ NoEligibleImages title) pure $ imagesFor nsfw info
let undir = joinPath (replicate (length (splitPath dir)) "..")
let formattedDate = formatLong date
let buttonBar = makeButtonBar title $ addIds images
let image0 :| otherImages = allImages images
let download0 = fromMaybe (bigFile image0) image0.download
let path0' = pageFile image0
let artistSection = makeArtist artist
let descSection = makeDesc $ descFor nsfw info
let tagsList = makeTags undir $ tagsFor nsfw info
let linksList = extLinks $ linksFor nsfw info
let updates = sort $ updatesFor nsfw info
let updatesList = makeUpdates updates
let makePrefetch img = [b||]
where path' = bigFile img
let prefetches = map makePrefetch otherImages
let makeWarning w = [b|@0
updated $updated|]
let nsfw' = NsfwWarning.Single <$ guard nsfw
let nsfwScript = NsfwWarning.script nsfw'
let nsfwDialog = NsfwWarning.dialog nsfw'
let imageMeta =
if image0.sfw && isNothing image0.warning then [b|@0
|] else [b|@0
|]
pure [b|@0
$imageMeta
$nsfwScript
$bgStyle
$0.prefetches