add support for categorised alts

This commit is contained in:
Rhiannon Morris 2021-08-23 16:30:11 +02:00
parent e47b790242
commit 2ccfb72b22
4 changed files with 68 additions and 31 deletions

View File

@ -25,7 +25,7 @@ dependSingle' :: FilePath -> Info -> FilePath -> FilePath -> Bool -> Builder
dependSingle' yamlDir info prefix build nsfw = dependSingle' yamlDir info prefix build nsfw =
[b|$page: $deps $$(MAKEPAGES)|] [b|$page: $deps $$(MAKEPAGES)|]
where where
images = if nsfw then #images info else #sfwImages info images = #all if nsfw then #images info else #sfwImages info
paths = map #path images paths = map #path images
dls = mapMaybe #download images dls = mapMaybe #download images

View File

@ -2,7 +2,8 @@
module Info module Info
(Info (..), (Info (..),
tagsFor, descFor, imagesFor, linksFor, updatesFor, compareFor, sortFor, tagsFor, descFor, imagesFor, linksFor, updatesFor, compareFor, sortFor,
Artist (..), Image (..), Desc (..), DescField (..), Link (..), Update (..), Artist (..), Images' (..), Images, Image (..), Desc (..), DescField (..),
Link (..), Update (..),
GalleryInfo (..), GalleryFilters (..), ArtistFilter (..), NsfwFilter (..), GalleryInfo (..), GalleryFilters (..), ArtistFilter (..), NsfwFilter (..),
IndexInfo (..), IndexInfo (..),
readArtistFilter, matchArtist, readNsfwFilter, matchNsfw, matchFilters, readArtistFilter, matchArtist, readNsfwFilter, matchNsfw, matchFilters,
@ -31,6 +32,7 @@ import qualified Data.Text as Text
import Data.YAML (FromYAML (..), (.:), (.:?), (.!=)) import Data.YAML (FromYAML (..), (.:), (.:?), (.!=))
import qualified Data.YAML as YAML import qualified Data.YAML as YAML
import System.FilePath ((</>), takeBaseName, takeExtension, splitExtension) import System.FilePath ((</>), takeBaseName, takeExtension, splitExtension)
import Data.Bifunctor (second)
data Info = data Info =
@ -51,7 +53,7 @@ data Info =
desc :: !Desc, desc :: !Desc,
nsfwDesc :: !Desc, nsfwDesc :: !Desc,
bg :: !(Maybe Text), bg :: !(Maybe Text),
images :: ![Image], images :: !Images,
thumb' :: !(Maybe FilePath), thumb' :: !(Maybe FilePath),
links :: ![Link], links :: ![Link],
extras :: ![FilePath] extras :: ![FilePath]
@ -84,6 +86,14 @@ data Image =
} }
deriving (Eq, Show) deriving (Eq, Show)
data Images' a =
Uncat [a] -- ^ uncategorised
| Cat [(Text, [a])] -- ^ categorised
deriving (Eq, Show, Functor, Foldable, Traversable)
type Images = Images' Image
data Link = data Link =
Link { Link {
title :: !Text, title :: !Text,
@ -105,12 +115,21 @@ instance HasField "sfw" Image Bool where getField = not . #nsfw
instance HasField "sfw" Link Bool where getField = not . #nsfw instance HasField "sfw" Link Bool where getField = not . #nsfw
instance HasField "sfw" Update Bool where getField = not . #nsfw instance HasField "sfw" Update Bool where getField = not . #nsfw
instance HasField "sfwImages" Info [Image] where instance HasField "all" (Images' a) [a] where
getField = filter #sfw . #images getField (Uncat is) = is
instance HasField "nsfwImages" Info [Image] where getField (Cat cats) = foldMap snd cats
getField = filter #nsfw . #images
instance HasField "allNsfw" Info Bool where getField = null . #sfwImages filterImages :: (a -> Bool) -> Images' a -> Images' a
instance HasField "allSfw" Info Bool where getField = null . #nsfwImages filterImages p (Uncat is) = Uncat $ filter p is
filterImages p (Cat cats) =
Cat $ filter (not . null . snd) $ map (second $ filter p) cats
instance HasField "sfwImages" Info Images where
getField = filterImages #sfw . #images
instance HasField "nsfwImages" Info Images where
getField = filterImages #nsfw . #images
instance HasField "allNsfw" Info Bool where getField = null . #all . #sfwImages
instance HasField "allSfw" Info Bool where getField = null . #all . #nsfwImages
instance HasField "anySfw" Info Bool where getField = not . #allNsfw instance HasField "anySfw" Info Bool where getField = not . #allNsfw
instance HasField "anyNsfw" Info Bool where getField = not . #allSfw instance HasField "anyNsfw" Info Bool where getField = not . #allSfw
@ -125,7 +144,8 @@ instance HasField "nsfwUpdates" Info [Update] where
getField = filter #nsfw . #updates getField = filter #nsfw . #updates
instance HasField "thumb" Info (Maybe FilePath) where instance HasField "thumb" Info (Maybe FilePath) where
getField (Info {thumb', images}) = thumb' <|> #path <$> find #sfw images getField (Info {thumb', images}) =
thumb' <|> #path <$> find #sfw (#all images)
instance HasField "mine" Info Bool where getField = isNothing . #artist instance HasField "mine" Info Bool where getField = isNothing . #artist
instance HasField "notMine" Info Bool where getField = isJust . #artist instance HasField "notMine" Info Bool where getField = isJust . #artist
@ -181,7 +201,7 @@ descFor nsfw (Info {desc, nsfwDesc}) = if nsfw then desc <> nsfwDesc else desc
tagsFor :: Bool -> Info -> [Text] tagsFor :: Bool -> Info -> [Text]
tagsFor nsfw i = if nsfw then nub (#tags i <> #nsfwTags i) else #tags i tagsFor nsfw i = if nsfw then nub (#tags i <> #nsfwTags i) else #tags i
imagesFor :: Bool -> Info -> [Image] imagesFor :: Bool -> Info -> Images
imagesFor nsfw = if nsfw then #images else #sfwImages imagesFor nsfw = if nsfw then #images else #sfwImages
linksFor :: Bool -> Info -> [Link] linksFor :: Bool -> Info -> [Link]
@ -233,7 +253,7 @@ instance FromYAML Info where
<*> m .:? "desc" .!= NoDesc <*> m .:? "desc" .!= NoDesc
<*> m .:? "nsfw-desc" .!= NoDesc <*> m .:? "nsfw-desc" .!= NoDesc
<*> m .:? "bg" <*> m .:? "bg"
<*> (m .: "images" >>= imageList) <*> m .: "images"
<*> m .:? "thumb" <*> m .:? "thumb"
<*> m .:? "links" .!= [] <*> m .:? "links" .!= []
<*> m .:? "extras" .!= [] <*> m .:? "extras" .!= []
@ -261,7 +281,7 @@ instance FromYAML Image where
unlabelledImage :: YAML.Node YAML.Pos -> YAML.Parser Image unlabelledImage :: YAML.Node YAML.Pos -> YAML.Parser Image
unlabelledImage = unlabelledImage' Nothing unlabelledImage = unlabelledImage' Nothing
unlabelledImage' :: Maybe Text -> YAML.Node YAML.Pos -> YAML.Parser Image unlabelledImage' :: Maybe Text -> YAML.Node YAML.Pos -> YAML.Parser Image
unlabelledImage' label' y = asStr y <|> asObj y unlabelledImage' label' y = asStr y <|> asObj y
where where
asStr = YAML.withStr "path" \(Text.unpack -> path) -> asStr = YAML.withStr "path" \(Text.unpack -> path) ->
@ -278,6 +298,11 @@ unlabelledImage' label' y = asStr y <|> asObj y
pathToLabel = Text.pack . gapToSpace . takeBaseName pathToLabel = Text.pack . gapToSpace . takeBaseName
gapToSpace = map \case '-' -> ' '; '_' -> ' '; c -> c gapToSpace = map \case '-' -> ' '; '_' -> ' '; c -> c
instance FromYAML Images where
parseYAML y = Uncat <$> imageList y
<|> Cat <$> YAML.withSeq "list of categories" fromPairs y
where fromPairs = traverse $ withPairM \label -> fmap (label,) . imageList
instance FromYAML Link where instance FromYAML Link where
parseYAML = parseYAML =
withPairM \title rest -> asStr title rest <|> asObj title rest withPairM \title rest -> asStr title rest <|> asObj title rest

View File

@ -47,8 +47,8 @@ make' root prefix nsfw dataDir dir info@(Info {date, title, artist, bg}) = do
let buttonBar = makeButtonBar title images let buttonBar = makeButtonBar title images
let (image0@(Image {path = path0, download = download0'}), let (image0@(Image {path = path0, download = download0'}),
Size {width = width0, height = height0}) Size {width = width0, height = height0}) : otherImages
= head images = #all images
let download0 = fromMaybe path0 download0' let download0 = fromMaybe path0 download0'
let path0' = pageFile path0 let path0' = pageFile path0
let tinyCls = if any (tiny . #second) images then [b| class=tiny|] else "" let tinyCls = if any (tiny . #second) images then [b| class=tiny|] else ""
@ -60,7 +60,7 @@ make' root prefix nsfw dataDir dir info@(Info {date, title, artist, bg}) = do
let updatesList = makeUpdates updates let updatesList = makeUpdates updates
let makePrefetch (Image {path}) = [b|<link rel=prefetch href=$path>|] let makePrefetch (Image {path}) = [b|<link rel=prefetch href=$path>|]
let prefetches = map (makePrefetch . #first) $ tail images let prefetches = map (makePrefetch . #first) otherImages
let makeWarning w = [b|@0 let makeWarning w = [b|@0
<figcaption id=cw aria-role=button tabindex=0> <figcaption id=cw aria-role=button tabindex=0>
@ -195,24 +195,35 @@ makeDesc (LongDesc fs) = [b|@0
</div> </div>
|] |]
makeButtonBar :: Strict.Text -> [(Image, Size)] -> Builder makeButtonBar :: Strict.Text -> Images' (Image, Size) -> Builder
makeButtonBar title images = makeButtonBar title images =
case images of case images of
[] -> throw $ NoEligibleImages title Uncat [] -> throw $ NoEligibleImages title
[_] -> "" Uncat [_] -> ""
_ -> [b|@0 Cat [(_,[_])] -> ""
<nav id=alts aria-label="alternate versions"> Uncat imgs -> makeNav "uncat" $ makeAlts imgs
Cat cats -> makeNav "cat" $ map (uncurry makeCat) cats
where
makeNav (cls :: Text) inner = [b|@0
<nav id=alts class=$cls aria-label="alternate versions">
$2.inner
</nav> |]
makeCat lbl imgs = [b|@0
<section>
<h3 class=alt-cat>$lbl</h3>
$0.alts
</section> |]
where alts = makeAlts imgs
makeAlts imgs = [b|@0
<ul class="buttonbar bb-choice"> <ul class="buttonbar bb-choice">
$4.alts $2.elems
</ul> </ul> |]
</nav> where elems = map (uncurry altButton) imgs
|]
where alts = map (\(i, (im, sz)) -> altButton i im sz) $ zip [0..] images
altButton :: Int -> Image -> Size -> Builder altButton :: Image -> Size -> Builder
altButton i img size = [b|@0 altButton img size = [b|@0
<li$nsfwClass> <li$nsfwClass>
<input type=radio$checked name=variant id="$idLabel" value="$path'" <input type=radio name=variant id="$idLabel" value="$path'"
data-link="$link"$warning' data-link="$link"$warning'
data-width=$width data-height=$height> data-width=$width data-height=$height>
<label for="$idLabel"$nsfwLabelClass>$label</label> <label for="$idLabel"$nsfwLabelClass>$label</label>
@ -222,7 +233,6 @@ altButton i img size = [b|@0
Size {width, height} = size Size {width, height} = size
nsfwClass = if nsfw then [b| class=nsfw|] else "" nsfwClass = if nsfw then [b| class=nsfw|] else ""
nsfwLabelClass = if nsfw then [b| class=nsfw-label|] else "" nsfwLabelClass = if nsfw then [b| class=nsfw-label|] else ""
checked = if i == 0 then [b| checked|] else ""
idLabel = escId label idLabel = escId label
path' = pageFile path path' = pageFile path
link = fromMaybe path download link = fromMaybe path download
@ -297,7 +307,7 @@ imageSize dir img = do
Just (width, height) -> pure $ Size {width, height} Just (width, height) -> pure $ Size {width, height}
Nothing -> fail $ "couldn't understand identify output:\n" ++ output Nothing -> fail $ "couldn't understand identify output:\n" ++ output
withSizes :: FilePath -> [Image] -> IO [(Image, Size)] withSizes :: Traversable t => FilePath -> t Image -> IO (t (Image, Size))
withSizes dir = traverse \img -> do withSizes dir = traverse \img -> do
size <- imageSize dir $ #path img size <- imageSize dir $ #path img
pure (img, size) pure (img, size)

View File

@ -32,6 +32,7 @@ executable make-pages
ConstraintKinds, ConstraintKinds,
DataKinds, DataKinds,
DeriveAnyClass, DeriveAnyClass,
DeriveTraversable,
DerivingStrategies, DerivingStrategies,
DerivingVia, DerivingVia,
DuplicateRecordFields, DuplicateRecordFields,
@ -46,6 +47,7 @@ executable make-pages
PatternSynonyms, PatternSynonyms,
QuasiQuotes, QuasiQuotes,
RankNTypes, RankNTypes,
ScopedTypeVariables,
StandaloneDeriving, StandaloneDeriving,
TupleSections, TupleSections,
TypeSynonymInstances, TypeSynonymInstances,