Compare commits

..

3 Commits
🎨 ... ginger

Author SHA1 Message Date
Rhiannon Morris 92b198afce tweaks in Date 2021-08-24 10:43:42 +02:00
Rhiannon Morris b8970b6436 remove BuilderQQ from Date 2021-08-24 10:43:42 +02:00
Rhiannon Morris 2485e3e234 add ToGVal instances 2021-08-24 10:43:40 +02:00
27 changed files with 678 additions and 904 deletions

View File

@ -10,7 +10,6 @@ ROOT := https://gallery.niss.website
SMALL := 200
MEDW := 1000
MEDH := 1200
BIG := 3000
MAKEPAGES := $(TMPDIR)/make-pages
@ -40,7 +39,7 @@ $(BUILDDIR)/index.html: $(DATADIR)/index.yaml $(MAKEPAGES)
$(BUILDDIR)/%: %
$(call copy,--link --force)
$(call copy)
$(BUILDDIR)/%: $(TMPDIR)/%
$(call copy,--link)
@ -52,9 +51,6 @@ $(TMPDIR)/%_small.png: $(DATADIR)/%.png
$(TMPDIR)/%_med.png: $(DATADIR)/%.png
$(call resize,$(MEDW),$(MEDH),>)
$(TMPDIR)/%_big.png: $(DATADIR)/%.png
$(call resize,$(BIG),$(BIG),>)
$(TMPDIR)/%_small.jpg: $(DATADIR)/%.jpg
$(call resize,$(SMALL),$(SMALL),^,-gravity center -crop 1:1+0)
@ -62,19 +58,6 @@ $(TMPDIR)/%_small.jpg: $(DATADIR)/%.jpg
$(TMPDIR)/%_med.jpg: $(DATADIR)/%.jpg
$(call resize,$(MEDW),$(MEDH),>)
$(TMPDIR)/%_big.jpg: $(DATADIR)/%.jpg
$(call resize,$(BIG),$(BIG),>)
$(TMPDIR)/%_small.webp: $(DATADIR)/%.webp
$(call resize,$(SMALL),$(SMALL),^,-gravity center -crop 1:1+0)
$(TMPDIR)/%_med.webp: $(DATADIR)/%.webp
$(call resize,$(MEDW),$(MEDH),>)
$(TMPDIR)/%_big.webp: $(DATADIR)/%.webp
$(call resize,$(BIG),$(BIG),>)
$(MAKEPAGES): make-pages/*.hs make-pages/make-pages.cabal
echo "[make-pages]"
@ -94,14 +77,13 @@ include $(TMPDIR)/index.mk
endif
.PHONY: clean mostlyclean distclean
mostlyclean:
.PHONY: clean distclean
clean:
echo "[clean $(BUILDDIR)]"
rm -rf $(BUILDDIR)
clean: mostlyclean
distclean: clean
echo "[clean $(TMPDIR)]"
rm -rf $(TMPDIR)
distclean: clean
echo "[cabal clean]"
cabal --verbose=0 v2-clean
@ -157,19 +139,17 @@ endef
# args:
# 1. gallery prefix
# 2. index filename
# 3. build dir
# 4. data dir
# 5. other flags
# 2. build dir
# 3. data dir
# 4. other flags
define depend-single
echo "[deps] "$@
mkdir -p "$(dir $@)"
$(MAKEPAGES) $(MPFLAGS) depend-single $(5) \
$(MAKEPAGES) $(MPFLAGS) depend-single $(4) \
--output "$@" \
--prefix "$(1)" \
--index "$(2)" \
--build-dir "$(3)" \
--data-dir "$(4)" $<
--build-dir "$(2)" \
--data-dir "$(3)" $<
endef
# args
@ -190,16 +170,14 @@ endef
# args:
# 1. data dir
# 2. gallery prefix
# 3. index file
# 4. other flags
# 3. other flags
define single
echo "[single] "$@
mkdir -p "$(dir $@)"
$(MAKEPAGES) $(MPFLAGS) single $(4) \
$(MAKEPAGES) $(MPFLAGS) single $(3) \
--root $(ROOT) \
--data-dir "$(1)" \
--prefix "$(2)" \
--index "$(3)" \
--output "$@" \
$<
endef

View File

@ -2,14 +2,14 @@
module BuilderQQ
(b,
Builder, toStrictText, toLazyText, fromText, fromString, fromChar,
textMap, ifJust, escId, escAttr, CanBuild (..))
textMap, ifJust, escId, escAttr)
where
import Data.Char (isLower, isSpace, isDigit, isAlphaNum)
import Language.Haskell.TH
import Language.Haskell.TH.Quote
import Data.List (intersperse)
import Data.Maybe (mapMaybe, fromMaybe)
import Data.Maybe (mapMaybe)
import Data.Text.Lazy.Builder
(Builder, fromText, fromLazyText, fromString, singleton, toLazyText)
import Text.Read (readMaybe)
@ -43,7 +43,7 @@ reindentB i (toLazyText -> str) =
dropIndent = LText.drop minIndent
minIndent =
getMin $ fromMaybe 0 $ foldMap (Just . Min . indentOf) ls'
getMin $ option 0 id $ foldMap (Option . Just . Min . indentOf) ls'
indentOf = go 0 where
go n (' ' :.. cs) = go (n + 1) cs
@ -69,8 +69,8 @@ chunks = reverse . go "" [] . trimEnd where
go acc cs ('$' :. rest@(d :. _)) | isDigit d =
go "" ((Var (Reindent n), var) : lit acc : cs) rest3
where
(read . Text.unpack -> n, rest2) = Text.span isDigit rest
(var, rest3) = splitVar $ Text.tail rest2
((read . Text.unpack -> n), '.' :. rest2) = Text.span isDigit rest
(var, rest3) = splitVar rest2
-- $var: expands to that var's contents
go acc cs ('$' :. rest) =

View File

@ -1,28 +1,36 @@
module Date
(Date (..),
Day (..), dayNum, exact,
formatLong, formatShort, formatRSS, formatSlash, formatTooltip,
formatLong, formatShort, formatRSS, formatSlash,
parseP, parseS, parseA)
where
import Records ()
import Control.Applicative
import qualified Text.ParserCombinators.ReadP as ReadP
import Text.ParserCombinators.ReadP (ReadP, readS_to_P, readP_to_S, (<++))
import Data.Time hiding (Day)
import Data.Char (isSpace, toLower)
import BuilderQQ
import Data.Char (isSpace)
import Data.Function (on)
import Data.Functor
import Data.Maybe (fromMaybe)
import Data.YAML (FromYAML (..))
import qualified Data.YAML as YAML
import Data.Text (unpack)
import Text.Ginger (GVal, ToGVal (..), (~>))
import qualified Text.Ginger as Ginger
import qualified Text.Ginger.Html as Ginger
import Data.Text (Text, pack, unpack)
import Data.Text.Lazy (toStrict)
import Data.Text.Lazy.Builder (Builder)
import qualified Data.Text.Lazy.Builder as Builder
data Date = Date {year, month :: Int, day :: Day}
data Date = Date {year, month :: !Int, day :: !Day}
deriving (Eq, Ord, Show)
data Day =
Exact Int
| Approx Int
Exact !Int
| Approx !Int
| Unknown
deriving (Eq, Show)
@ -37,75 +45,67 @@ exact :: Day -> Bool
exact (Exact _) = True
exact _ = False
formatLong :: Date -> Builder
formatLong :: Date -> Text
formatLong (Date {year, month, day}) =
case dayN of
toText case dayN of
Nothing -> monthYear
Just (nth -> d) -> [b|$approx$weekday $d $monthYear|]
Just (nth -> d) -> mconcat [approx, weekday, " ", d, " ", monthYear]
where
dayN = dayNum day
day' = fromMaybe 1 dayN
formatted str = fromString $
formatTime defaultTimeLocale str $
fromGregorian (toInteger year) month day'
monthYear = formatted "%B %Y"
weekday = formatted "%a"
approx = if exact day then "" else [b|approx. $&|]
approx = if exact day then "" else "approx. "
dayN = dayNum day
day' = fromMaybe 1 dayN
monthYear = formatted "%B %Y"
weekday = formatted "%a"
greg = fromGregorian (toInteger year) month day'
formatted str = Builder.fromString $ formatTime defaultTimeLocale str greg
formatShort :: Date -> Builder
formatShort (Date {month, day}) = [b|$day'$month'|] where
formatShort :: Date -> Text
formatShort (Date {month, day}) = toText $ day' <> month' where
day' = case day of
Exact d -> [b|$d $&|]
Approx d -> [b|$d? $&|]
Unknown -> ""
month' = formatTime defaultTimeLocale "%b" $ fromGregorian 1 month 1
formatTooltip :: Date -> Builder
formatTooltip (Date {year, month, day}) = [b|$day'$month' $year|] where
day' = case day of
Exact d -> [b|$d $&|]
Approx d -> [b|$d? $&|]
Unknown -> ""
month' = map toLower $
Exact d -> bshow d <> " "
Approx d -> bshow d <> "? "
Unknown -> mempty
month' = Builder.fromString $
formatTime defaultTimeLocale "%b" $ fromGregorian 1 month 1
formatRSS :: Date -> Builder
formatRSS = fromString . format . toTime where
formatRSS :: Date -> Text
formatRSS = pack . format . toTime where
format = formatTime defaultTimeLocale "%a, %d %b %_Y %T GMT"
toTime (Date {year, month, day}) =
let year' = toInteger year; day' = fromMaybe 1 $ dayNum day in
UTCTime (fromGregorian year' month day') 15600
where
year' = toInteger year
day' = fromMaybe 1 $ dayNum day
formatSlash :: Date -> Builder
formatSlash (Date {year, month, day}) = case dayNum day of
Nothing -> [b|$year/$month|]
Just d -> [b|$year/$month/$d$q|]
where q = if exact day then "" else [b|<span class=q>?</span>|]
formatSlash :: Date -> Text
formatSlash (Date {year, month, day}) =
toText $ mconcat [bshow year, "/", bshow month, "/", bshow day', bshow ex]
where day' = dayNum day; ex = exact day
nth :: Int -> Builder
nth n = [b|$n$suf|] where
suf | n >= 10, n <= 19 = [b|th|]
| n `mod` 10 == 1 = [b|st|]
| n `mod` 10 == 2 = [b|nd|]
| n `mod` 10 == 3 = [b|rd|]
| otherwise = [b|th|]
nth n = bshow n <> suf where
suf | n >= 10, n <= 19 = "th"
| n `mod` 10 == 1 = "st"
| n `mod` 10 == 2 = "nd"
| n `mod` 10 == 3 = "rd"
| otherwise = "th"
parseP :: ReadP Date
parseP = do
year <- readp
char_ '-'
dash
month <- readp
day <- option Unknown do
char_ '-'
dash
d <- readp
approx <- option Exact (Approx <$ ReadP.char '?')
approx <- option Exact $ ReadP.char '?' $> Approx
pure $ approx d
pure $ Date year month day
pure $ Date {year, month, day}
where
readp = readS_to_P reads
char_ c = () <$ ReadP.char c
option k p = p <++ pure k
dash = void $ ReadP.char '-'
option k p = p <++ return k
parseS :: ReadS Date
parseS = readP_to_S parseP
@ -118,3 +118,26 @@ parseA str = case parseS str of
instance FromYAML Date where
parseYAML = YAML.withStr "date" $ parseA . unpack
instance ToGVal m Date where
toGVal d@(Date {year, month, day=day'}) =
dict {Ginger.asText = long, Ginger.asHtml = Ginger.html long}
where
dict = Ginger.dict
["year" ~> year, "month" ~> month, "day" ~> day, "exact" ~> exact day',
"long" ~> long, "short" ~> short, "rss" ~> rss, "slash" ~> slash]
day :: GVal m
day = case day' of
Exact x -> toGVal x
Approx x -> toGVal $ show x <> "?"
Unknown -> "?"
long = formatLong d
short = formatShort d
rss = formatRSS d
slash = formatSlash d
toText :: Builder -> Text
toText = toStrict . Builder.toLazyText
bshow :: Show a => a -> Builder
bshow = Builder.fromString . show

View File

@ -1,10 +1,10 @@
module Depend
(dependSingle, dependSingle',
dependGallery, dependGallery',
thumbFile, pageFile, bigFile)
thumbFile, pageFile)
where
import BuilderQQ hiding (CanBuild (..))
import BuilderQQ
import Info hiding (Text)
import Data.Maybe (fromMaybe, mapMaybe)
@ -13,19 +13,17 @@ import System.FilePath
dependSingle :: FilePath -- ^ yaml file name (relative to data dir!)
-> FilePath -- ^ index file name
-> Info
-> FilePath -- ^ output prefix
-> FilePath -- ^ build dir
-> Bool -- ^ include nsfw?
-> Text
dependSingle yamlDir indexFile info prefix build nsfw =
toLazyText $ dependSingle' yamlDir indexFile info prefix build nsfw
dependSingle yamlDir info prefix build nsfw =
toLazyText $ dependSingle' yamlDir info prefix build nsfw
dependSingle' :: FilePath -> FilePath -> Info -> FilePath -> FilePath -> Bool
-> Builder
dependSingle' yamlDir indexFile info prefix build nsfw =
[b|$page: $deps $indexFile $$(MAKEPAGES)|]
dependSingle' :: FilePath -> Info -> FilePath -> FilePath -> Bool -> Builder
dependSingle' yamlDir info prefix build nsfw =
[b|$page: $deps $$(MAKEPAGES)|]
where
images = #all if nsfw then #images info else #sfwImages info
@ -36,10 +34,7 @@ dependSingle' yamlDir indexFile info prefix build nsfw =
dir = build </> prefix </> yamlDir
page = dir </> "index.html"
deps = unwords $ map (dir </>) $
thumbFile (thumbnail info) :
map pageFile paths ++
map bigFile paths ++
dls ++ extras
thumbFile (thumbnail info) : map pageFile paths ++ paths ++ dls ++ extras
dependGallery :: GalleryInfo
-> FilePath -- ^ index file
@ -81,25 +76,24 @@ dependGallery' (GalleryInfo {prefix, filters})
gallery = build </> prefix </> "index.html"
rss = build </> prefix </> "rss.xml"
rules = makeRules prefix indexFile filters build data_ tmp
rules = makeRules prefix filters build data_ tmp
inc d = tmp </> prefix </> takeDirectory d <.> "mk"
incFiles = unwords $ map inc files
incs = if null infos then "" else [b|include $incFiles|]
makeRules :: FilePath -- ^ prefix
-> FilePath -- ^ index file
-> GalleryFilters
-> FilePath -- ^ build dir
-> FilePath -- ^ data dir
-> FilePath -- ^ tmp dir
-> Builder
makeRules prefix indexFile filters build data_ tmp = [b|@0
makeRules prefix filters build data_ tmp = [b|@0
$buildPrefix/%/index.html: $data_/%/info.yaml $$(MAKEPAGES)
$$(call single,$data_,$prefix,$indexFile,$flags)
$$(call single,$data_,$prefix,$flags)
$tmpPrefix/%.mk: $data_/%/info.yaml $$(MAKEPAGES)
$$(call depend-single,$prefix,$indexFile,$build,$data_,$flags)
$$(call depend-single,$prefix,$build,$data_,$flags)
$buildPrefix/%: $tmp/%
$$(call copy,-l)

View File

@ -6,14 +6,12 @@ import Date
import Info
import qualified NsfwWarning
import Control.Monad
import Data.Foldable
import Data.Function (on, (&))
import qualified Data.HashMap.Strict as HashMap
import Data.HashSet (HashSet)
import qualified Data.HashSet as HashSet
import Data.List (intersperse, groupBy, sortBy, sort)
import Data.Maybe
import Data.List (intersperse, groupBy, sortBy, sortOn)
import qualified Data.Text.Lazy as Lazy
import System.FilePath (takeDirectory, joinPath, splitPath)
import GHC.Exts (Down (..), the)
@ -40,8 +38,6 @@ make' root (GalleryInfo {title, desc, prefix, filters, hidden}) infos = [b|@0
<meta name=twitter:site content=@2_gecs>
<meta name=twitter:card content=summary>
<meta name=robots content='noai,noimageai'>
<script src=/script/gallery.js></script>
$0.nsfwScript
@ -52,8 +48,9 @@ make' root (GalleryInfo {title, desc, prefix, filters, hidden}) infos = [b|@0
<div class=page>
<header>
<h1>$title</h1>
<a class="right corner" href=rss.xml>rss</a>
<a class="left corner" href=$undir>back</a>
<h2 class="right corner">
<a href=rss.xml>rss</a>
</h2>
</header>
<nav id=filters>
@ -61,21 +58,17 @@ make' root (GalleryInfo {title, desc, prefix, filters, hidden}) infos = [b|@0
<summary><h2>filters</h2></summary>
<div>
<h3>show only</h3>
<ul id=require class=filterlist>
<ul id=require class="buttonbar bb-choice">
$10.requireFilters
</ul>
<h3>exclude</h3>
<ul id=exclude class=filterlist>
<ul id=exclude class="buttonbar bb-choice">
$10.excludeFilters
</ul>
<ul id=filterstuff>
<li><a href=# id=clear>clear</a>
<li><a href=# id=sortalpha>sort by name</a>
<li><a href=# id=sortuses>sort by uses</a>
<li><a href=# id=singles>toggle single-use tags</a>
</ul>
<a href=# id=clear>clear</a>
<a href=# id=singles>toggle single-use tags</a>
</div>
</details>
</nav>
@ -85,6 +78,10 @@ make' root (GalleryInfo {title, desc, prefix, filters, hidden}) infos = [b|@0
$6.items
</ul>
</main>
<footer>
<a href=$undir>all galleries</a>
</footer>
</div>
|]
where
@ -93,7 +90,6 @@ make' root (GalleryInfo {title, desc, prefix, filters, hidden}) infos = [b|@0
infosByYear =
[(the year, infopath) |
infopath@(_, info) <- infos,
not $ #unlisted info,
then sortInfo by info,
let year = #latestYear info nsfw,
then group by Down year using groupBy']
@ -105,7 +101,7 @@ make' root (GalleryInfo {title, desc, prefix, filters, hidden}) infos = [b|@0
allTags = infos
& concatMap (map (,1) . tagsFor nsfw . #second)
& HashMap.fromListWith (+) & HashMap.toList
& sort
& sortOn (\(tag, count) -> (Down count, tag))
requireFilters = map (uncurry $ makeFilter "require" mempty) allTags
excludeFilters = map (uncurry $ makeFilter "exclude" hidden) allTags
@ -117,9 +113,8 @@ make' root (GalleryInfo {title, desc, prefix, filters, hidden}) infos = [b|@0
| (_, (p0, i0) : _) : _ <- infosByYear = getThumb (takeDirectory p0) i0
| otherwise = "/style/card.png"
nsfw' = NsfwWarning.Gallery <$ guard nsfw
nsfwScript = NsfwWarning.script nsfw'
nsfwDialog = NsfwWarning.dialog nsfw'
nsfwScript = NsfwWarning.script nsfw
nsfwDialog = NsfwWarning.dialog nsfw
makeFilter :: Text -> HashSet Text -> Text -> Int -> Builder
makeFilter prefix initial tag count = [b|@0
@ -147,26 +142,27 @@ makeYearItems nsfw year infos = [b|@0
year' = show year & foldMap \c -> [b|<span class=y>$c</span>|]
makeItem :: Bool -> FilePath -> Info -> Builder
makeItem nsfw file info@(Info {bg}) = [b|@0
<li class="item post$nsfw'" data-year=$year' data-updated="$updated'"
makeItem nsfw file info@(Info {title, bg}) = [b|@0
<li class="item post$nsfw'" data-date="$date'" data-year=$year'
data-updated="$updated'"
data-tags="$tags'">
<a href="$dir">
<img src="$thumb" loading=lazy$bgStyle
width=200 height=200
title="$tooltip">
</a>
<figure>
<a href="$dir">
<img src="$thumb" loading=lazy$bgStyle>
</a>
<figcaption>
<span class=date>$date'</span>
<span class=title>$title</span>
</figcaption>
</figure>
|]
where
title = fromMaybe (#title info) $ #galleryTitle info
dir = takeDirectory file
thumb = getThumb dir info
nsfw' = if nsfw && #anyNsfw info then [b| nsfw|] else ""
tags' = fold $ intersperse ";" $ map fromText $ tagsFor nsfw info
date = #latestDate info nsfw
date' = formatTooltip date
date' = formatShort date
year' = #year date
updated' = if #updated info nsfw then [b|true|] else [b|false|]
bgStyle = case bg of Other col -> [b| style="background: $col"|]; _ -> ""
tooltip =
let upd = if #updated info nsfw then "updated " else "" :: Builder in
[b|$title ($upd$date')|]
bgStyle = ifJust bg \col -> [b| style="background: $col"|]

View File

@ -27,8 +27,6 @@ make' root (IndexInfo {title, desc, galleries, links, footer}) = [b|@0
<meta name=twitter:site content=@2_gecs>
<meta name=twitter:card content=summary>
<meta name=robots content='noai,noimageai'>
<title>$title</title>
<div class=page>

View File

@ -1,16 +1,13 @@
{-# OPTIONS_GHC -fdefer-typed-holes #-}
{-# OPTIONS_GHC -Wno-orphans #-}
module Info
(Info (..),
tagsFor, descFor, imagesFor, linksFor, updatesFor, lastUpdate,
compareFor, sortFor,
tagsFor, descFor, imagesFor, linksFor, updatesFor, compareFor, sortFor,
Artist (..), Images' (..), Images, Image (..), Desc (..), DescField (..),
Link (..), Update (..), Bg (..),
Link (..), Update (..),
GalleryInfo (..), GalleryFilters (..), ArtistFilter (..), NsfwFilter (..),
IndexInfo (..),
readArtistFilter, matchArtist, readNsfwFilter, matchNsfw, matchFilters,
NoThumb (..), getThumb, thumbFile, pageFile, bigFile,
NoThumb (..), getThumb, thumbFile, pageFile,
-- ** Reexports
Date (..), Day (..), Text)
where
@ -26,8 +23,7 @@ import Data.Hashable (Hashable)
import Data.HashSet (HashSet)
import qualified Data.HashSet as HashSet
import qualified Data.Map.Strict as Map
import Data.Set (Set, (\\))
import qualified Data.Set as Set
import qualified Data.HashMap.Strict as HashMap
import Data.Maybe (isJust, isNothing, fromMaybe, mapMaybe)
import Data.List (nub, sortBy)
import Data.Ord (comparing)
@ -36,41 +32,37 @@ import Data.Text (Text)
import qualified Data.Text as Text
import Data.YAML (FromYAML (..), (.:), (.:?), (.!=))
import qualified Data.YAML as YAML
import Text.Ginger (GVal, ToGVal (..), (~>))
import qualified Text.Ginger as Ginger
import System.FilePath ((</>), takeBaseName, takeExtension, splitExtension)
import Data.Bifunctor (second)
data Info =
Info {
date :: !Date,
date :: !Date,
-- | extra sort key after date
-- e.g. multiple things on the same day might have a,b,c in @sortEx@ to
-- put them in the right order in the gallery
sortEx :: !Text,
updates :: ![(Date, [Update])],
sortEx :: !Text,
updates :: ![Update],
-- | if false, don't show updated emblem even if @updates@ is non-empty
showUpdated :: !Bool,
-- | hide from gallery view
unlisted :: !Bool,
title :: !Text,
galleryTitle :: !(Maybe Text),
artist :: !(Maybe Artist), -- nothing = me, obv
nsfwOnly :: !Bool,
tags :: ![Text],
nsfwTags :: ![Text],
desc :: !Desc,
nsfwDesc :: !Desc,
bg :: !Bg,
images :: !Images,
thumb' :: !(Maybe FilePath),
links :: ![Link],
extras :: ![FilePath]
showUpdated :: !Bool,
title :: !Text,
artist :: !(Maybe Artist), -- nothing = me, obv
nsfwOnly :: !Bool,
tags :: ![Text],
nsfwTags :: ![Text],
desc :: !Desc,
nsfwDesc :: !Desc,
bg :: !(Maybe Text),
images :: !Images,
thumb' :: !(Maybe FilePath),
links :: ![Link],
extras :: ![FilePath]
}
deriving (Eq, Show)
data Bg = Default | NoBorder | Other !Text
deriving (Eq, Show)
data Desc =
NoDesc
| TextDesc !Text
@ -115,6 +107,7 @@ data Link =
data Update =
Update {
date :: !Date,
desc :: !Text,
nsfw :: !Bool,
ignoreSort :: !Bool
@ -148,10 +141,10 @@ instance HasField "sfwLinks" Info [Link] where
instance HasField "nsfwLinks" Info [Link] where
getField = filter #nsfw . #links
instance HasField "sfwUpdates" Info [(Date, [Update])] where
getField = filter (not . null) . map (second (filter #sfw)) . #updates
instance HasField "nsfwUpdates" Info [(Date, [Update])] where
getField = filter (not . null) . map (second (filter #nsfw)) . #updates
instance HasField "sfwUpdates" Info [Update] where
getField = filter #sfw . #updates
instance HasField "nsfwUpdates" Info [Update] where
getField = filter #nsfw . #updates
instance HasField "thumb" Info (Maybe FilePath) where
getField (Info {thumb', images}) =
@ -163,15 +156,15 @@ instance HasField "notMine" Info Bool where getField = isJust . #artist
instance HasField "latestDate" Info (Bool -> Date) where
getField info@(Info {date=date}) nsfw =
maximum $ date : mapMaybe relDate (updatesFor nsfw info)
where relDate (date, us) = date <$ guard (not $ any #ignoreSort us)
where relDate (Update {date, ignoreSort}) = date <$ guard (not ignoreSort)
instance HasField "latestYear" Info (Bool -> Int) where
getField info nsfw = #year $ #latestDate info nsfw
instance HasField "updated" Info (Bool -> Bool) where
getField (Info {updates, showUpdated}) nsfw = showUpdated && updated where
updated = if nsfw then not $ null updates else any (any #sfw . snd) updates
getField (Info {updates, showUpdated}) nsfw = showUpdated && updated
where updated = if nsfw then not $ null updates else any #sfw updates
defDescKey :: Text
defDescKey = "about"
@ -217,13 +210,9 @@ imagesFor nsfw = if nsfw then #images else #sfwImages
linksFor :: Bool -> Info -> [Link]
linksFor nsfw = if nsfw then #links else #sfwLinks
updatesFor :: Bool -> Info -> [(Date, [Update])]
updatesFor :: Bool -> Info -> [Update]
updatesFor nsfw = if nsfw then #updates else #sfwUpdates
lastUpdate :: Bool -> Info -> Maybe Date
lastUpdate nsfw info =
case updatesFor nsfw info of [] -> Nothing; us -> Just $ fst $ last us
compareFor :: Bool -> Info -> Info -> Ordering
compareFor nsfw = comparing \i -> (#latestDate i nsfw, #sortEx i, #title i)
@ -247,81 +236,124 @@ pageFile f
| takeExtension f == ".gif" = f
| otherwise = addSuffix "_med" f
bigFile :: FilePath -> FilePath
bigFile f
| takeExtension f == ".gif" = f
| otherwise = addSuffix "_big" f
addSuffix :: String -> FilePath -> FilePath
addSuffix suf path =
let (pre, ext) = splitExtension path in
pre ++ suf ++ ext
getKeys :: YAML.Mapping YAML.Pos -> YAML.Parser (Set Text)
getKeys = fmap Set.fromList . traverse (YAML.withStr "key" pure) . Map.keys
checkKeys :: YAML.Mapping YAML.Pos -> Set Text -> YAML.Parser ()
checkKeys mapping wanted = do
keys <- getKeys mapping
let unused = Set.toList $ keys \\ wanted
unless (null unused) do
fail $ "unused keys: " <> show unused <> "\n" <>
"expected: " <> show wanted
instance FromYAML Info where
parseYAML = YAML.withMap "info" \m -> do
checkKeys m ["date", "sort", "updates", "show-updated", "unlisted",
"gallery-title", "title", "artist", "nsfw-only", "tags",
"nsfw-tags", "desc", "nsfw-desc", "bg", "images", "thumb",
"links", "extras"]
parseYAML = YAML.withMap "info" \m ->
Info <$> m .: "date"
<*> m .:? "sort" .!= ""
<*> (m .:? "updates" >>= updateList)
<*> m .:? "show-updated" .!= True
<*> m .:? "unlisted" .!= False
<*> m .: "title"
<*> m .:? "gallery-title"
<*> m .:? "artist"
<*> m .:? "nsfw-only" .!= False
<*> m .:? "tags" .!= []
<*> m .:? "nsfw-tags" .!= []
<*> m .:? "desc" .!= NoDesc
<*> m .:? "nsfw-desc" .!= NoDesc
<*> m .:? "bg" .!= Default
<*> m .:? "bg"
<*> m .: "images"
<*> m .:? "thumb"
<*> m .:? "links" .!= []
<*> m .:? "extras" .!= []
instance FromYAML Bg where
parseYAML y =
YAML.withNull "default value" (pure Default) y
<|> YAML.withStr "css <image> or \"noborder\""
(\str -> pure if str == "noborder" then NoBorder else Other str) y
instance MonadFail m => ToGVal m Info where
toGVal i = Ginger.dict
["date" ~> #date i,
"sortEx" ~> #sortEx i,
"updates" ~> #updates i,
"sfwUpdates" ~> #sfwUpdates i,
"nsfwUpdates" ~> #nsfwUpdates i,
"showUpdated" ~> #showUpdated i,
"title" ~> #title i,
"artist" ~> #artist i,
"mine" ~> #mine i,
"notMine" ~> #notMine i,
"nsfwOnly" ~> #nsfwOnly i,
"tags" ~> #tags i,
"nsfwTags" ~> #nsfwTags i,
"desc" ~> #desc i,
"nsfwDesc" ~> #nsfwDesc i,
"bg" ~> #bg i,
"hasCat" ~> case #images i of Cat _ -> True; Uncat _ -> False,
"images" ~> #images i,
"sfwImages" ~> #sfwImages i,
"nsfwImages" ~> #nsfwImages i,
"allNsfw" ~> #allNsfw i,
"allSfw" ~> #allSfw i,
"anyNsfw" ~> #anyNsfw i,
"anySfw" ~> #anySfw i,
"thumb" ~> #thumb i,
"links" ~> #links i,
"sfwLinks" ~> #sfwLinks i,
"nsfwLinks" ~> #nsfwLinks i,
"extras" ~> #extras i,
"updated" ~> nsfwFunc "updated" (#updated i),
"latestDate" ~> nsfwFunc "latestDate" (#latestDate i),
"latestYear" ~> nsfwFunc "latestYear" (#latestYear i)]
where
nsfwFunc :: ToGVal m b => String -> (Bool -> b) -> GVal m
nsfwFunc name f = Ginger.fromFunction \args -> do
let (args, pos, rest) = Ginger.matchFuncArgs ["nsfw"] args
unless (null pos) do
fail $ name <> ": extra positional args"
unless (HashMap.null rest) do
fail $ name <> ": extra named args " <> show (HashMap.keys rest)
nsfw <- case HashMap.lookup "nsfw" args of
Nothing -> fail $ name <> ": missing argument 'nsfw'"
Just x -> Ginger.fromGValM x
pure $ toGVal $ f nsfw
instance Monad m => ToGVal m Images where
toGVal (Uncat imgs) = toGVal imgs
toGVal (Cat cats) = Ginger.dict $ second toGVal <$> cats
instance FromYAML Artist where
parseYAML y = justName y <|> withUrl y where
justName = YAML.withStr "name" \name -> pure $ Artist {name, url = Nothing}
withUrl = YAML.withMap "full info" \m -> do
checkKeys m ["name", "url"]
withUrl = YAML.withMap "full info" \m ->
Artist <$> m .: "name" <*> m .:? "url"
instance ToGVal m Artist where
toGVal (Artist {name, url}) = Ginger.dict ["name" ~> name, "url" ~> url]
instance FromYAML Desc where
parseYAML y = textDesc y <|> mapDesc y where
textDesc = YAML.withStr "text" $ pure . TextDesc
mapDesc = fmap LongDesc . parseYAML
instance ToGVal m Desc where
toGVal NoDesc = toGVal ()
toGVal (TextDesc txt) = toGVal $ LongDesc [DescField defDescKey txt]
toGVal (LongDesc d) = Ginger.dict [k ~> v | DescField k v <- d]
instance FromYAML DescField where parseYAML = withPair DescField
imageList :: YAML.Node YAML.Pos -> YAML.Parser [Image]
imageList y = pure <$> unlabelledImage y <|> parseYAML y
instance FromYAML Image where
parseYAML y = unlabelledImage y <|> labelled y where
labelled = withPairM \label -> unlabelledImage' (Just label)
instance ToGVal m Image where
toGVal i = Ginger.dict
["label" ~> #label i,
"path" ~> #path i,
"download" ~> #download i,
"nsfw" ~> #nsfw i,
"sfw" ~> #sfw i,
"warning" ~> #warning i]
imageList :: YAML.Node YAML.Pos -> YAML.Parser [Image]
imageList y = pure <$> unlabelledImage y <|> parseYAML y
unlabelledImage :: YAML.Node YAML.Pos -> YAML.Parser Image
unlabelledImage = unlabelledImage' Nothing
@ -333,7 +365,6 @@ unlabelledImage' label' y = asStr y <|> asObj y
pure $ Image {label, path, download = Nothing,
nsfw = False, warning = Nothing}
asObj = YAML.withMap "image info" \m -> do
checkKeys m ["path", "download", "nsfw", "warning"]
path <- m .: "path"
download <- m .:? "download"
nsfw <- m .:? "nsfw" .!= False
@ -355,29 +386,39 @@ instance FromYAML Link where
asStr title = YAML.withStr "url" \url ->
pure $ Link {title, url, nsfw = False}
asObj title = YAML.withMap "link info" \m -> do
checkKeys m ["url", "nsfw"]
url <- m .: "url"
nsfw <- m .:? "nsfw" .!= False
pure $ Link {title, url, nsfw}
instance ToGVal m Link where
toGVal l = Ginger.dict
["title" ~> #title l,
"url" ~> #url l,
"nsfw" ~> #nsfw l,
"sfw" ~> #sfw l]
updateList :: Maybe (YAML.Node YAML.Pos) -> YAML.Parser [(Date, [Update])]
instance ToGVal m Update where
toGVal u = Ginger.dict
["date" ~> #date u,
"desc" ~> #desc u,
"nsfw" ~> #nsfw u,
"sfw" ~> #sfw u]
updateList :: Maybe (YAML.Node YAML.Pos) -> YAML.Parser [Update]
updateList =
maybe (pure []) $ YAML.withMap "updates" $ traverse bodies . Map.toList
maybe (pure []) $ YAML.withMap "updates" $ traverse asEither . Map.toList
where
bodies (date', rest) = (,) <$> parseYAML date' <*> body rest
body b =
return <$> body1 b
<|> YAML.withSeq "update list" (traverse body1) b
body1 b = asDesc b <|> asObj b
asDesc = YAML.withStr "desc" \desc ->
pure $ Update {desc, nsfw = False, ignoreSort = False}
asObj = YAML.withMap "update info" \m -> do
checkKeys m ["desc", "nsfw", "ignore-sort"]
asEither (date', rest) = do
date <- parseYAML date'
asDesc date rest <|> asObj date rest
asDesc date = YAML.withStr "desc" \desc ->
pure $ Update {date, desc, nsfw = False, ignoreSort = False}
asObj date = YAML.withMap "update info" \m -> do
desc <- m .: "desc"
nsfw <- m .:? "nsfw" .!= False
ignoreSort <- m .:? "ignore-sort" .!= False
pure $ Update {desc, nsfw, ignoreSort}
pure $ Update {date, desc, nsfw, ignoreSort}
data GalleryInfo =
@ -445,8 +486,7 @@ matchFilters (GalleryFilters {nsfw, artist, require, exclude}) i =
instance FromYAML GalleryInfo where
parseYAML = YAML.withMap "gallery info" \m -> do
checkKeys m ["title", "desc", "prefix", "filters", "hidden"]
parseYAML = YAML.withMap "gallery info" \m ->
GalleryInfo <$> m .: "title"
<*> m .: "desc"
<*> m .: "prefix"
@ -454,8 +494,7 @@ instance FromYAML GalleryInfo where
<*> m .:? "hidden" .!= mempty
instance FromYAML GalleryFilters where
parseYAML = YAML.withMap "gallery filters" \m -> do
checkKeys m ["nsfw", "artist", "require", "exclude"]
parseYAML = YAML.withMap "gallery filters" \m ->
GalleryFilters <$> m .:? "nsfw" .!= AllN
<*> m .:? "artist" .!= AllA
<*> m .:? "require" .!= []
@ -476,8 +515,7 @@ data IndexInfo =
deriving Show
instance FromYAML IndexInfo where
parseYAML = YAML.withMap "index info" \m -> do
checkKeys m ["title", "desc", "galleries", "links", "footer"]
parseYAML = YAML.withMap "index info" \m ->
IndexInfo <$> m .: "title"
<*> m .: "desc"
<*> m .:? "galleries" .!= []

View File

@ -47,12 +47,11 @@ main = do
main2 mode
main2 :: HasVerbose => ModeOptions -> IO ()
main2 (SinglePage {root, file, prefix, index, dataDir, nsfw, output}) = do
siteName <- #title <$> readYAML @IndexInfo index
main2 (SinglePage {root, file, prefix, dataDir, nsfw, output}) = do
info <- readYAML file
printV $ "contents" := info
let dir = takeDirectory $ makeRelative dataDir file
page <- SinglePage.make root siteName prefix nsfw dataDir dir info
page <- SinglePage.make root prefix nsfw dataDir dir info
writeOutput output page
main2 (GalleryPage {root, files, prefix, index, output, dataDir}) = do
@ -78,12 +77,12 @@ main2 (RSS {files, root, index, prefix, output, dataDir}) = do
let rss = RSS.make root ginfo output' infos
writeOutput output rss
main2 (DependSingle {index, file, nsfw, output, prefix, buildDir, dataDir}) = do
main2 (DependSingle {file, nsfw, output, prefix, buildDir, dataDir}) = do
info <- readYAML file
printV $ "contents" := info
let dir = takeDirectory $ makeRelative dataDir file
printV $ "dir" := dir
let deps = dependSingle dir index info prefix buildDir nsfw
let deps = dependSingle dir info prefix buildDir nsfw
writeOutput output deps
main2 (DependGallery {file, output, buildDir, dataDir, tmpDir, infoName}) = do

View File

@ -1,42 +1,27 @@
module NsfwWarning (What (..), script, dialog) where
module NsfwWarning (script, dialog) where
import BuilderQQ
script :: Bool -> Builder
script False = ""
script True = [b|<script src=/script/nsfw-warning.js></script>|]
data What = Single | Gallery
instance CanBuild What where
build Single = "this art"
build Gallery = "some of the art in this gallery"
script :: Maybe What -> Builder
script Nothing = ""
script (Just _) = [b|<script src=/script/nsfw-warning.js></script>|]
dialog :: Maybe What -> Builder
dialog Nothing = ""
dialog (Just what) = [b|@0
dialog :: Bool -> Builder
dialog False = ""
dialog True = [b|@0
<div class=dialog id=nsfw-dialog>
<div class=dialog-inner>
<h1>cw: lewd art</h1>
<h1>cw: lewd</h1>
<img class=dialog-icon src=/style/stop_hand.svg>
<div class=dialog-message>
<p>
$what contains pornographic content that is
<strong>not suitable for minors</strong>.
<p>
by continuing, you are confirming that you are at least
<strong>eighteen years old</strong>.
are you an adult? <br> if not please don't look!
</div>
<div class=dialog-buttons>
<button id=nsfw-yes class=yes>i am an adult</button>
<a href=//crouton.net referrerpolicy=no-referrer>
<button id=nsfw-no class=no>i am not</button>
</a>
<button id=nsfw-yes class=yes>yes i am and i wanna see</button>
<button id=nsfw-no class=no>no im not</button>
</div>
</div>
</div>

View File

@ -15,7 +15,6 @@ data ModeOptions =
root :: Text,
file :: FilePath,
prefix :: FilePath,
index :: FilePath,
dataDir :: FilePath,
nsfw :: Bool,
output :: Maybe FilePath
@ -46,7 +45,6 @@ data ModeOptions =
nsfw :: Bool,
output :: Maybe FilePath,
prefix :: FilePath,
index :: FilePath,
buildDir :: FilePath,
dataDir :: FilePath
}
@ -82,8 +80,7 @@ optionsParser = globalOpts `info` mainInfo where
single = command "single" $ singleOpts `info` singleInfo
singleOpts =
SinglePage <$> root <*> file <*> prefix <*> indexFile
<*> dataDir <*> nsfwS <*> output
SinglePage <$> root <*> file <*> prefix <*> dataDir <*> nsfwS <*> output
root = strOption $
short 'R' <> long "root" <> metavar "URL" <>
help "website root (no trailing slash)"
@ -93,9 +90,6 @@ optionsParser = globalOpts `info` mainInfo where
short 'p' <> long "prefix" <> metavar "DIR" <>
value "" <>
help "gallery directory prefix"
indexFile = strOption $
short 'i' <> long "index" <> metavar "FILE" <>
help "path to index file"
nsfwS = switch $
short 'n' <> long "nsfw" <>
help "include nsfw versions"
@ -113,6 +107,9 @@ optionsParser = globalOpts `info` mainInfo where
galleryOpts =
GalleryPage <$> root <*> files <*> prefix
<*> indexFile <*> output <*> dataDir
indexFile = strOption $
short 'i' <> long "index" <> metavar "FILE" <>
help "path to index file"
files = many $ strArgument $
metavar "FILE..." <> help "yaml files to read"
galleryInfo = progDesc "generate a gallery page"
@ -125,7 +122,7 @@ optionsParser = globalOpts `info` mainInfo where
dependSingle = command "depend-single" $ dsOpts `info` dsInfo
dsOpts =
DependSingle <$> file <*> nsfwS <*> output <*> prefix
<*> indexFile <*> buildDir <*> dataDir
<*> buildDir <*> dataDir
buildDir = strOption $
short 'B' <> long "build-dir" <> metavar "DIR" <> value "_build" <>
help "build directory (default: _build)"

View File

@ -40,24 +40,22 @@ make' root ginfo@(GalleryInfo {title, desc, prefix}) output infos = [b|@0
link = [b|$root/$prefix|]
nsfw = #nsfw ginfo
items = map (uncurry $ makeItem root prefix nsfw) $
sortBy (flip (compareFor nsfw `on` #second)) $
filter (not . #unlisted . snd) infos
sortBy (flip (compareFor nsfw `on` #second)) infos
selflink = case output of
Nothing -> ""
Just o -> [b|<atom:link href="$link/$o" rel="self" />|]
makeItem :: Strict.Text -> FilePath -> Bool -> FilePath -> Info -> Builder
makeItem root prefix nsfw path i@(Info {title, artist}) = [b|@4
makeItem root prefix nsfw path i@(Info {title, date, artist}) = [b|@4
<item>
<title>$title$up</title>
<title>$title</title>
<link>$link</link>
<guid>$link</guid>
$descArtist'
<pubDate>$date</pubDate>
<pubDate>$date'</pubDate>
</item>
|]
where
up = if #updated i nsfw then [b| (updated)|] else ""
dir = takeDirectory path
link = [b|$root/$prefix/$dir|]
artist' = ifJust artist \case
@ -68,18 +66,18 @@ makeItem root prefix nsfw path i@(Info {title, artist}) = [b|@4
descArtist' = if #exists desc || isJust artist then [b|@6
<description>
<![CDATA[
$10.artist'
$10.desc'
$10.artist'
]]>
</description>
|]
else ""
date = formatRSS $ #latestDate i nsfw
date' = formatRSS date
makeDesc :: Desc -> Builder
makeDesc NoDesc = ""
makeDesc (TextDesc txt) = [b|$txt|]
makeDesc (LongDesc fs) = [b|<dl>$fields</dl>|]
makeDesc (LongDesc fs) = [b|$fields|]
where
fields = map makeField fs
makeField (DescField {name, text}) = [b|<dt>$name <dd>$text|]
makeField (DescField {name, text}) = [b|<b>$name</b>: $text|]

View File

@ -1,5 +1,5 @@
{-# OPTIONS_GHC -Wno-orphans #-}
{-# LANGUAGE MultiParamTypeClasses, ScopedTypeVariables, TypeApplications #-}
{-# LANGUAGE TypeApplications #-}
module Records (HasField (..)) where
import GHC.Records

View File

@ -7,18 +7,19 @@ import Records ()
import qualified NsfwWarning
import Control.Exception
import Control.Monad
import Data.List (sort, intersperse)
import Data.Maybe (fromMaybe, isNothing, isJust)
import Data.List (sort)
import Data.Maybe (fromMaybe)
import qualified Data.Text as Strict
import qualified Data.Text.Lazy as Lazy
import System.FilePath (joinPath, splitPath)
import System.FilePath (joinPath, splitPath, (</>))
import qualified System.Process as Proc
import Text.Read (readMaybe)
import qualified Data.HashSet as Set
import Data.Traversable
-- | e.g. only nsfw images are present for a non-nsfw page
newtype NoEligibleImages = NoEligibleImages {title :: Strict.Text}
data NoEligibleImages = NoEligibleImages {title :: !Strict.Text}
deriving stock Eq deriving anyclass Exception
instance Show NoEligibleImages where
@ -28,20 +29,17 @@ instance Show NoEligibleImages where
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 root prefix nsfw dataDir dir info =
toLazyText <$> make' root 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
let images = imagesFor nsfw info
make' :: Text -> FilePath -> Bool -> FilePath -> FilePath -> Info -> IO Builder
make' root prefix nsfw dataDir dir info@(Info {date, title, artist, bg}) = do
images <- withSizes (dataDir </> dir) $ imagesFor nsfw info
let undir = joinPath (replicate (length (splitPath dir)) "..")
@ -50,13 +48,12 @@ make' root siteName prefix nsfw _dataDir dir
let formattedDate = formatLong date
let buttonBar = makeButtonBar title $ addIds images
let allImages = #all images
let image0@(Image {path = path0, download = download0'}) = head allImages
let otherImages = tail allImages
let download0 = fromMaybe (bigFile path0) download0'
let (image0@(Image {path = path0, download = download0'}),
Size {width = width0, height = height0}) : otherImages
= #all images
let download0 = fromMaybe path0 download0'
let path0' = pageFile path0
let tinyCls = if any (tiny . #second) images then [b| class=tiny|] else ""
let descSection = makeDesc $ descFor nsfw info
let tagsList = makeTags undir $ tagsFor nsfw info
@ -64,9 +61,8 @@ make' root siteName prefix nsfw _dataDir dir
let updates = sort $ updatesFor nsfw info
let updatesList = makeUpdates updates
let makePrefetch (Image {path}) = [b|<link rel=prefetch href=$path'>|]
where path' = bigFile path
let prefetches = map makePrefetch otherImages
let makePrefetch (Image {path}) = [b|<link rel=prefetch href=$path>|]
let prefetches = map (makePrefetch . #first) otherImages
let makeWarning w = [b|@0
<figcaption id=cw aria-role=button tabindex=0>
@ -74,30 +70,17 @@ make' root siteName prefix nsfw _dataDir dir
</figcaption>
|]
let defWarning = [b|
i forgot to add a cw, sorry! <br>
if you can let me know i'd appreciate it
|]
let defWarning = "oops i forgot to put one, sorry!<br>\
\if you can let me know i'd appreciate it" :: Text
let warning'
| Just w <- #warning image0 = makeWarning w
| #nsfw image0 = makeWarning defWarning
| otherwise = mempty
let warningT = makeWarning [b|.|]
let bgStyle = case bg of
Default -> ""
NoBorder -> [b|@0
<style>
#mainfig {
background: transparent;
border: none;
box-shadow: none;
}
</style>
|]
Other col -> [b|@0
<style> #mainfig { background: $col; } </style>
|]
let bgStyle = ifJust bg \col -> [b|@0
<style> #mainfig { background: $col; } </style>
|]
let url = [b|$root/$prefix/$dir|]
let desc = case artist of
@ -105,23 +88,12 @@ make' root siteName prefix nsfw _dataDir dir
Nothing -> "by niss"
let thumb = getThumb "" info
let updateDate = ifJust (last' updates) \(d, _) ->
let updateDate = ifJust (last' updates) \(Update {date = d}) ->
let updated = formatLong d in
[b|<br> <span class=updated>updated $updated</span>|]
let nsfw' = NsfwWarning.Single <$ guard nsfw
let nsfwScript = NsfwWarning.script nsfw'
let nsfwDialog = NsfwWarning.dialog nsfw'
let imageMeta =
if #sfw image0 && isNothing (#warning image0) then [b|@0
<meta property=og:image content="$url/$path0'">
<meta name=twitter:card content=summary_large_image>
<meta name=twitter:image content="$url/$path0'">
|] else [b|@0
<meta property=og:image content="$url/$thumb">
<meta name=twitter:card content=summary>
|]
let nsfwScript = NsfwWarning.script nsfw
let nsfwDialog = NsfwWarning.dialog nsfw
pure [b|@0
<!DOCTYPE html>
@ -131,15 +103,14 @@ make' root siteName prefix nsfw _dataDir dir
<link rel=stylesheet href=/style/shiny/single.css>
<link rel=icon href=/style/niss.svg>
<meta property=og:type content=article>
<meta property=og:type content=og:website>
<meta property=og:title content="$title">
<meta property=og:site_name content="$siteName">
<meta property=og:site_name content="$title">
<meta property=og:description content="$desc">
<meta property=og:image content="$url/$thumb">
<meta property=og:url content="$url">
<meta name=twitter:site content=@2_gecs>
$imageMeta
<meta name=robots content='noai,noimageai'>
<meta name=twitter:card content=summary>
<script src=/script/single.js></script>
$nsfwScript
@ -154,19 +125,16 @@ make' root siteName prefix nsfw _dataDir dir
<div class=page>
<header>
<h1>$title</h1>
$artistTag
<h2 id=date class="right corner">
$formattedDate $updateDate
</h2>
<h2 class="left corner">
$artistTag
<a href=$undir>back to gallery</a>
</h2>
</header>
$2.buttonBar
<main>
<figure id=mainfig>
<figure id=mainfig data-width=$width0 data-height=$height0$tinyCls>
$warning'
<a id=mainlink href="$download0" title="download full version">
<img id=mainimg src="$path0'" alt="">
@ -176,13 +144,17 @@ make' root siteName prefix nsfw _dataDir dir
<div id=info>
$6.descSection
$6.updatesList
$6.tagsList
$6.linksList
$6.tagsList
$6.updatesList
</div>
</main>
<footer>
<a href=$undir>back to gallery</a>
</footer>
</div>
<template id=cw-template>
@ -195,7 +167,7 @@ last' xs = if null xs then Nothing else Just $ last xs
makeArtist :: Artist -> Builder
makeArtist (Artist {name, url}) =
[b|by $artistLink <br>|]
[b|<h2 id=artist class="left corner">by $artistLink</h2>|]
where
artistLink = case url of
Just u -> [b|<a href="$u">$name</a>|]
@ -225,72 +197,53 @@ makeDesc (LongDesc fs) = [b|@0
</div>
|]
addIds :: Traversable t => t Image -> t (Image, Text)
addIds :: Images' (Image, a) -> Images' (Image, a, Text)
addIds = snd . mapAccumL makeId Set.empty where
makeId used img = (Set.insert newId used, (img, newId)) where
makeId used (img, x) = (Set.insert newId used, (img, x, newId)) where
newId = head $ filter (\i -> not $ i `Set.member` used) ids
ids = [toStrictText [b|$label$i|] | i <- "" : map show [0::Int ..]]
label = escId $ #label img
makeButtonBar :: Strict.Text -> Images' (Image, Text) -> Builder
makeButtonBar :: Strict.Text -> Images' (Image, Size, Text) -> Builder
makeButtonBar title images =
case images of
Uncat [] -> throw $ NoEligibleImages title
Uncat [_] -> ""
Cat [(_,[_])] -> ""
Uncat imgs -> makeNav "uncat" $ makeAlts imgs
Cat cats
| all ((<= 1) . length . snd) cats ->
makeButtonBar title $ Uncat $ flatten cats
| [(_, imgs)] <- cats ->
makeButtonBar title (Uncat imgs)
| otherwise ->
makeNav "cat" $ map (uncurry makeCat) cats
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
$2.skipAll
</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">
$2.elems
</ul> |]
where elems = map (uncurry altButton) imgs
skipAll =
if any (isJust . #warning . fst) images then
[b|@0
<div class=buttonbar id=skipAllDiv>
<input type=checkbox name=skipAll id=skipAll>
<label for=skipAll>skip warnings</label>
</div>
|]
else
""
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">
$2.elems
</ul> |]
where elems = map (\(img,sz,i) -> altButton img sz i) imgs
flatten :: [(Text, [(Image, a)])] -> [(Image, Text)]
flatten cats =
addIds [(img {label = cat}) | (cat, is) <- cats, (img, _) <- is]
altButton :: Image -> Text -> Builder
altButton img i = [b|@0
altButton :: Image -> Size -> Text -> Builder
altButton img size i = [b|@0
<li$nsfwClass>
<input type=radio name=variant id="$i" value="$path'"
data-link="$link"$warning'>
data-link="$link"$warning'
data-width=$width data-height=$height>
<label for="$i"$nsfwLabelClass>$label</label>
|]
where
Image {label, path, nsfw, warning, download} = img
Size {width, height} = size
nsfwClass = if nsfw then [b| class=nsfw|] else ""
nsfwLabelClass = if nsfw then [b| class=nsfw-label|] else ""
path' = pageFile path
link = fromMaybe (bigFile path) download
link = fromMaybe path download
warning' = ifJust warning \(escAttr -> w) -> [b| data-warning="$w"|]
makeTags :: FilePath -> [Strict.Text] -> Builder
@ -298,7 +251,7 @@ makeTags undir tags =
if null tags then "" else [b|@0
<nav id=tags class=info-section>
<h2>tags</h2>
<ul>
<ul class="buttonbar bb-links">
$4.tagList
</ul>
</nav>
@ -313,7 +266,7 @@ extLinks links =
if null links then "" else [b|@0
<nav id=links class=info-section>
<h2>links</h2>
<ul>
<ul class="buttonbar bb-links">
$4.linkList
</ul>
</nav>
@ -328,9 +281,9 @@ extLink (Link {title, url}) = [b|@8
</a>
|]
makeUpdates :: [(Date, [Update])] -> Builder
makeUpdates :: [Update] -> Builder
makeUpdates ups =
if all (null . snd) ups then "" else [b|@4
if null ups then "" else [b|@4
<section id=updates class=info-section>
<h2>updates</h2>
<dl>
@ -338,13 +291,31 @@ makeUpdates ups =
</dl>
</section>
|]
where updateList = map (uncurry makeUpdate) ups
where updateList = map makeUpdate ups
makeUpdate :: Date -> [Update] -> Builder
makeUpdate _ [] = ""
makeUpdate date ups = [b|@8
makeUpdate :: Update -> Builder
makeUpdate (Update {date, desc}) = [b|@8
<dt>$date'
<dd>$desc
|] where
date' = formatSlash date
desc = mconcat $ map fromText $ intersperse "; " $ map #desc ups
|]
where date' = formatSlash date
data Size = Size {width, height :: !Int} deriving (Eq, Show)
tiny :: Size -> Bool
tiny (Size {width, height}) = width < 250 || height < 250
imageSize :: FilePath -> FilePath -> IO Size
imageSize dir img = do
-- "[0]" to get the first frame of an animation
-- otherwise it prints a pair for each frame
let filename = (dir </> img) ++ "[0]"
output <- Proc.readProcess "identify" ["-format", "(%W,%H)", filename] ""
case readMaybe output of
Just (width, height) -> pure $ Size {width, height}
Nothing -> fail $ "couldn't understand identify output:\n" ++ output
withSizes :: Traversable t => FilePath -> t Image -> IO (t (Image, Size))
withSizes dir = traverse \img -> do
size <- imageSize dir $ #path img
pure (img, size)

View File

@ -40,6 +40,7 @@ executable make-pages
FlexibleInstances,
GeneralizedNewtypeDeriving,
LambdaCase,
MultiParamTypeClasses,
NamedFieldPuns,
OverloadedLabels,
OverloadedLists,
@ -55,22 +56,21 @@ executable make-pages
other-extensions:
CPP,
ImplicitParams,
MultiParamTypeClasses,
ScopedTypeVariables,
TemplateHaskell,
TransformListComp,
TypeApplications
build-depends:
base ^>= 4.16.4,
bytestring ^>= 0.11.3.1,
base >= 4.12.0.0 && < 4.15,
bytestring ^>= 0.10.8.2,
containers ^>= 0.6.0.1,
filemanip ^>= 0.3.6.3,
filepath ^>= 1.4.2.1,
ginger ^>= 0.10.1.0,
hashable ^>= 1.3.0.0,
HsYAML ^>= 0.2.1.0,
optparse-applicative ^>= 0.15.1.0,
process ^>= 1.6.8.2,
template-haskell ^>= 2.18.0.0,
template-haskell ^>= 2.16.0.0,
text ^>= 1.2.3.1,
time >= 1.8.0.2 && < 1.10,
unordered-containers ^>= 0.2.11.0

View File

@ -35,14 +35,6 @@ function updateItems() {
document.getElementById(`marker-${year}`).hidden = hide;
}
function disp(pfx, tags) {
return Array(...tags).map(x => pfx + x).join('\u2003'); // em space
}
let plus = disp('+\u2009', reqTags); // thin space
let minus = disp('-\u2009', excTags);
document.getElementById('filters-details').dataset.filters =
`${plus}\u2003${minus}`.trim();
}
function update() {
@ -67,7 +59,7 @@ function toggle(checkbox) {
function clearForm() {
allBoxes.forEach(b => b.checked = b.defaultChecked);
allBoxes.forEach(b => b.checked = false);
}
function clear(e) {
@ -79,8 +71,8 @@ function clear(e) {
function toggleSingles(e) {
showSingles = !showSingles;
for (let li of document.querySelectorAll('.filterlist li')) {
let count = +li.querySelector('label').dataset.count;
for (let li of document.querySelectorAll('#filters li')) {
let count = li.querySelector('label').dataset.count;
if (count <= 1) {
li.hidden = !showSingles;
}
@ -103,19 +95,15 @@ function makeFragment() {
function useFragment() {
let frag = decodeURIComponent(location.hash).replace(/^#/, '');
let details = document.getElementById('filters-details');
if (!frag) {
if (frag == 'all' || !frag) {
clearForm();
} else if (frag == 'all') {
allBoxes.forEach(b => b.checked = false);
details.open = false;
} else {
let set = new Set(frag.split(';'));
let re = /^(require|exclude)_|hide_filters/;
if (Array.from(set).every(x => re.test(x))) {
if (new Array(...set).every(x => /^(require|exclude)_/.test(x))) {
allBoxes.forEach(b => b.checked = set.has(b.id));
details.open = !frag.match(/hide_filters|example\b/);
let details = document.getElementById('filters-details');
details.open = !set.has('hide_filters');
}
}
@ -123,46 +111,6 @@ function useFragment() {
}
function sortFilters(cmp) {
function sort1(id) {
let elt = document.getElementById(id);
let children = [...elt.childNodes];
children.sort(cmp);
for (let c of children) {
elt.removeChild(c);
elt.appendChild(c);
}
}
sort1('require');
sort1('exclude');
}
function sortFiltersAlpha(e) {
function getName(x) {
if (x.nodeType == Node.ELEMENT_NODE) {
return x.getElementsByTagName('input')[0].value;
} else {
return '';
}
}
sortFilters((a, b) => getName(a).localeCompare(getName(b)));
e.preventDefault();
}
function sortFiltersUses(e) {
function getUses(x) {
if (x.nodeType == Node.ELEMENT_NODE) {
return parseInt(x.getElementsByTagName('label')[0].dataset.count);
} else {
return 0;
}
}
sortFilters((a, b) => getUses(b) - getUses(a));
e.preventDefault();
}
function setup() {
function inputs(id) {
let iter = document.getElementById(id).getElementsByTagName('input');
@ -170,8 +118,8 @@ function setup() {
}
let items = Array.from(document.getElementsByClassName('post'));
itemsByYear = new Map;
for (let item of items) {
let year = item.dataset.year;
if (!itemsByYear.has(year)) itemsByYear.set(year, new Set);
@ -187,13 +135,8 @@ function setup() {
allBoxes.forEach(b => b.addEventListener('change', () => toggle(b)));
function addClick(id, f) {
document.getElementById(id).addEventListener('click', f);
}
addClick('clear', clear);
addClick('sortalpha', sortFiltersAlpha);
addClick('sortuses', sortFiltersUses);
addClick('singles', toggleSingles);
document.getElementById('clear').addEventListener('click', clear);
document.getElementById('singles').addEventListener('click', toggleSingles);
window.addEventListener('popstate', useFragment);
@ -201,4 +144,5 @@ function setup() {
}
window.addEventListener('DOMContentLoaded', setup);
})();

View File

@ -17,19 +17,16 @@ function yes() {
dismiss();
}
// now just a normal link
/*
function no() {
document.location = '//crouton.net';
history.go(-1);
}
*/
function setup() {
if (alreadyYes()) {
dismiss();
} else {
document.getElementById('nsfw-yes').onclick = yes;
// document.getElementById('nsfw-no').onclick = no;
document.getElementById('nsfw-no').onclick = no;
}
}

View File

@ -5,11 +5,10 @@ let mainfig;
let mainimg;
let mainlink;
let altButtons;
let skipAll;
let opened = new Set;
function openCW(id, caption, focusLink = false) {
function openCW(id, caption, focusLink) {
if (id) opened.add(id);
mainfig.removeChild(caption);
mainlink.tabIndex = 0;
@ -24,13 +23,11 @@ function addCWListeners(id, caption) {
}
}
function setImage(id, src, href, cw) {
function setImage(id, src, width, height, href, cw, firstLoad) {
let caption = document.getElementById('cw');
let newCaption;
let checked = skipAll ? skipAll.checked : false;
if (!checked && !opened.has(id) && cw) {
if (!opened.has(id) && cw) {
newCaption = document.getElementById('cw-template')
.content.firstElementChild.cloneNode(true);
newCaption.querySelector('#cw-text').innerHTML = cw;
@ -45,13 +42,17 @@ function setImage(id, src, href, cw) {
mainlink.tabIndex = -1;
}
mainimg.src = src;
mainlink.href = href;
mainimg.src = src;
mainfig.dataset.width = width;
mainfig.dataset.height = height;
mainlink.href = href;
}
function activateButton(button, doPush = true) {
function activateButton(button, doPush = true, firstLoad = false) {
setImage(button.id, button.value,
button.dataset.link, button.dataset.warning);
button.dataset.width, button.dataset.height,
button.dataset.link, button.dataset.warning,
firstLoad);
if (doPush) history.pushState(null, '', '#' + button.id);
}
@ -70,7 +71,7 @@ function useFragment(firstLoad = false) {
if (button) {
id = button.id;
button.checked = true;
activateButton(button, false);
activateButton(button, false, firstLoad);
}
if (firstLoad) addCWListeners(id, document.getElementById('cw'));
@ -80,28 +81,15 @@ function setup() {
mainfig = document.getElementById('mainfig');
mainimg = document.getElementById('mainimg');
mainlink = document.getElementById('mainlink');
skipAll = document.getElementById('skipAll');
let alts = document.getElementById('alts');
if (alts) {
let inputs = Array.from(alts.getElementsByTagName('input'));
altButtons = inputs.filter(e => e.name == 'variant');
} else {
altButtons = [];
}
altButtons = alts ? Array.from(alts.getElementsByTagName('input')) : [];
for (let button of altButtons) {
button.onchange = e => { if (button.checked) activateButton(button); };
}
if (skipAll) {
skipAll.onchange = e => { if (skipAll.checked) {
let caption = document.getElementById('cw');
if (caption) { openCW(null, caption, false); }
} };
}
window.addEventListener('popstate', e => useFragment());
window.addEventListener('popstate', useFragment);
useFragment(true);
}

View File

@ -1,77 +0,0 @@
<?xml version="1.0" encoding="UTF-8" standalone="no"?>
<svg
xmlns:dc="http://purl.org/dc/elements/1.1/"
xmlns:cc="http://creativecommons.org/ns#"
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:svg="http://www.w3.org/2000/svg"
xmlns="http://www.w3.org/2000/svg"
xmlns:sodipodi="http://sodipodi.sourceforge.net/DTD/sodipodi-0.dtd"
xmlns:inkscape="http://www.inkscape.org/namespaces/inkscape"
width="100%"
height="100%"
viewBox="0 0 32 32"
version="1.1"
xml:space="preserve"
style="fill-rule:evenodd;clip-rule:evenodd;stroke-linecap:round;stroke-linejoin:round;stroke-miterlimit:10;"
id="svg13"
sodipodi:docname="checked.svg"
inkscape:version="1.0.2 (e86c870879, 2021-01-15)"><defs
id="defs17" /><sodipodi:namedview
pagecolor="#ffffff"
bordercolor="#666666"
borderopacity="1"
objecttolerance="10"
gridtolerance="10"
guidetolerance="10"
inkscape:pageopacity="0"
inkscape:pageshadow="2"
inkscape:window-width="2419"
inkscape:window-height="1748"
id="namedview15"
showgrid="false"
inkscape:zoom="22.34375"
inkscape:cx="16"
inkscape:cy="16"
inkscape:window-x="0"
inkscape:window-y="0"
inkscape:window-maximized="0"
inkscape:current-layer="emoji" />
<metadata
id="metadata2">
<rdf:RDF>
<rdf:Description
rdf:about="">
<dc:title>Mutant Standard emoji 2020.04</dc:title>
</rdf:Description>
<cc:work
rdf:about="">
<cc:license
rdf:resource="http://creativecommons.org/licenses/by-nc-sa/4.0/" />
<cc:attributionName>Dzuk</cc:attributionName>
<cc:attributionURL>http://mutant.tech/</cc:attributionURL>
</cc:work>
<cc:Work
rdf:about=""><dc:format>image/svg+xml</dc:format><dc:type
rdf:resource="http://purl.org/dc/dcmitype/StillImage" /></cc:Work></rdf:RDF>
</metadata>
<rect
id="large_blue_diamond"
x="0"
y="0"
width="32"
height="32"
style="fill:none;" /><g
id="outline"><path
d="M3,15l13,-13l13,13l0,2l-13,13l-13,-13l0,-2Z"
style="fill:none;stroke:#000;stroke-width:4px;"
id="path5" /></g><g
id="emoji"><path
d="M3,17l0,-2l13,-11l13,11l0,2l-13,13l-13,-13Z"
style="fill:#1598db;fill-opacity:1"
id="path8" /><path
d="M29,15l-13,13l-13,-13l13,-13l13,13Z"
style="fill:#6bddf4;fill-opacity:1"
id="path10" /></g></svg>

Before

Width:  |  Height:  |  Size: 2.3 KiB

View File

@ -1 +0,0 @@
<svg clip-rule="evenodd" fill-rule="evenodd" stroke-linejoin="round" stroke-miterlimit="2" viewBox="0 0 32 32" xmlns="http://www.w3.org/2000/svg"><metadata/><path d="m0 0h32v32h-32z" fill="none"/><path d="m2.449 7.008-.664-1.661c-.15-.391-.229-.801-.222-1.22.005-.288.049-.576.131-.852.27-.907.946-1.662 1.819-2.028.386-.162.797-.24 1.214-.247.074 0 .074.001.148.003.172.012.34.033.508.075.331.083.644.232.918.434.098.073.188.152.276.236l1.599 1.599.042-.001c.141-.003.14-.003.282-.002.376.009.749.042 1.119.111.84.155 1.649.472 2.37.931.371.236.713.51 1.034.811 1.371 1.34 2.705 2.717 4.068 4.064.354.342.732.656 1.139.933s.837.514 1.285.718c2.149.95 4.315 1.862 6.464 2.813.356.163.702.343 1.036.548.726.444 1.389.99 1.967 1.615.763.827 1.373 1.794 1.791 2.839.391.977.613 2.019.655 3.069.037.927-.066 1.858-.305 2.754-.522 1.958-1.696 3.724-3.273 4.992-.922.742-1.98 1.312-3.106 1.676-1.25.404-2.579.55-3.887.429-1.006-.093-1.996-.344-2.925-.741-.392-.168-.77-.363-1.138-.578-1.901-1.144-3.793-2.303-5.679-3.471-.771-.49-1.509-1.028-2.2-1.625-1.634-1.41-3.01-3.114-4.044-5.008-.402-.736-.753-1.5-1.048-2.285-.149-.396-.282-.797-.405-1.201-.482-1.65-.946-3.305-1.418-4.958-.07-.255-.129-.511-.171-.772-.082-.517-.102-1.043-.06-1.565.068-.846.3-1.677.68-2.435z"/><path d="m13 8 2.606 2.606c.921.921 2.007 1.661 3.201 2.18 1.573.684 3.956 1.721 6.266 2.725 1.812.788 3.223 2.28 3.91 4.132.686 1.852.589 3.903-.271 5.681-.001.001-.001.001-.001.002-.95 1.963-2.684 3.434-4.777 4.049-2.092.615-4.347.317-6.207-.82-1.802-1.101-3.699-2.26-5.389-3.293-3.433-2.098-5.951-5.409-7.057-9.277l-.781-2.735 1.995-6.002z" fill="#5c247c"/><path d="m13.05 11.001.084.003.083.008.083.011.083.014.082.018.081.021.08.024.079.028.077.031.077.035.075.037.073.041.071.044.07.046.068.05.065.052.063.055.061.058.058.06.056.062.053.065.051.067.047.069.045.071.041.073.039.074.035.076.032.077.029.079.029.084.023.066.025.065.024.066.026.064.027.065.027.064.028.063.028.064.03.062.03.063.031.061.032.062.032.061.033.061.034.06.035.059.035.06.036.058.037.059.037.058.038.057.039.057.04.056.04.056.041.055.041.055.042.054.043.054.043.054.044.052.045.052.045.052.046.051.047.051.047.05.048.049.048.049.05.048.049.048.05.047.051.046.051.046.052.045.053.045.053.044.054.043.054.043.055.042.055.041.056.041.056.04.057.039.057.039.058.038.059.038.059.036.059.036.06.036.061.034.061.034.061.033.062.033.068.034 5.166 2.583.075.039.072.042.071.045.068.048.067.051.064.054.062.056.06.059.057.061.055.064.052.065.049.068.046.07.043.072.04.074.037.075.034.076.031.078.027.079.024.081.02.081.018.082.013.083.011.083.006.083.004.084-.001.084-.003.083-.008.084-.01.083-.015.082-.017.082-.021.081-.025.081-.027.079-.032.077-.034.077-.037.075-.041.073-.043.072-.047.069-.049.068-.053.065-.055.064-.057.06-.06.059-.063.056-.064.053-.067.05-.069.048-.071.045-.073.041-.074.039-.076.035-.077.033-.079.029-.079.025-.081.023-.082.018-.082.016-.083.012-.083.008-.084.005-.084.002-.084-.002-.083-.006-.083-.008-.083-.013-.082-.016-.082-.019-.081-.023-.079-.026-.079-.03-.077-.032-.075-.036-5.178-2.589-.101-.051-.106-.056-.105-.056-.104-.058-.104-.059-.102-.061-.102-.061-.101-.063-.1-.064-.099-.065-.098-.066-.097-.068-.097-.068-.095-.07-.095-.071-.094-.072-.092-.073-.092-.074-.091-.075-.09-.076-.088-.077-.088-.079-.087-.079-.086-.081-.085-.081-.084-.082-.083-.084-.081-.084-.081-.086-.08-.086-.078-.087-.078-.089-.076-.089-.076-.09-.074-.091-.073-.092-.072-.093-.071-.094-.07-.094-.068-.096-.068-.096-.066-.098-.065-.098-.064-.098-.063-.1-.061-.101-.061-.101-.059-.102-.058-.103-.057-.104-.055-.104-.054-.105-.053-.106-.052-.107-.05-.107-.05-.108-.047-.109-.047-.109-.045-.11-.044-.111-.043-.111-.041-.112-.04-.113-.033-.099.001.003-.026-.08-.022-.08-.019-.082-.015-.082-.012-.083-.009-.084-.005-.083-.001-.084.002-.084.006-.083.009-.084.012-.082.016-.083.02-.081.023-.081.026-.079.029-.079.033-.077.036-.075.039-.075.042-.072.046-.07.048-.069.051-.067.053-.064.057-.062.058-.06.062-.057.063-.054.066-.052.068-.049.07-.046.072-.043.074-.04.075-.037.076-.034.078-.03.08-.028.08-.023.081-.021.082-.017.083-.014.083-.01.083-.007.084-.003.084.001z" fill="#8428bd"/><g fill="#219555"><path d="m4.5 13.25-.574-2.01c-.552-1.93.207-3.996 1.878-5.109 0 0 0-.001.001-.001 1.858-1.238 4.331-.994 5.91.585l1.285 1.285v1h-3l-1 3-3-1z"/><path d="m5 8s-.768-1.921-1.353-3.382c-.145-.363-.101-.775.119-1.1.219-.324.585-.518.977-.518h.003c.162 0 .319.065.434.18.647.647 2.82 2.82 2.82 2.82z"/></g></svg>

Before

Width:  |  Height:  |  Size: 4.3 KiB

View File

@ -1,8 +1,6 @@
@import url(/fonts/muller/muller.css);
:root {
/* old slightly-muted gradient */
/*
--gradient:
linear-gradient(135deg,
hsl(42deg, 67%, 70%),
@ -12,37 +10,24 @@
hsl(195deg, 67%, 67%),
hsl(155deg, 57%, 62%)
);
*/
/* bright colours from yummy.cricket bg */
--gradient:
linear-gradient(135deg,
hsl(42deg, 92%, 70%),
hsl(348deg, 92%, 70%),
hsl(334deg, 100%, 80%),
hsl(234deg, 100%, 76%),
hsl(195deg, 100%, 67%),
hsl(155deg, 70%, 62%)
);
--text-col: white;
--text-shadow-col: hsl(0, 0%, 0%, 75%);
--text-shadow: 2px 2px 3px var(--text-shadow-col);
--nsfw-sticker-rotate: 15deg;
--focus-box: 0 0 5px hsl(55deg, 60%, 90%, 80%);
--focus-box: 0 0 20px hsl(55deg, 60%, 90%, 80%);
--focus-text: hsl(334deg, 87%, 90%);
--shadow-col: hsl(42deg, 82%, 90%, 75%);
--border-col: var(--text-col);
--border: 3px solid var(--border-col);
--border-radius: 1.5em;
--shadow: 0 0 3em var(--shadow-col);
--background: hsla(0, 0%, 0%, 60%);
--button-bg: hsla(0deg, 0%, 0%, 20%);
--button-bg-selected: hsla(0deg, 0%, 100%, 20%);
--button-border: 1px solid hsla(0deg, 0%, 0%, 40%);
--button-border-selected: 1px solid hsla(0deg, 0%, 100%, 30%);
--button-pad: 0.15em 0.8em;
--button-radius: 1000px;
--button-bg: hsl(330deg, 40%, 16%, 100%);
--button-corner: 0.25em;
font-family: Muller;
font-size: x-large;
@ -52,8 +37,6 @@
margin: 0;
}
body { margin: 0; }
header {
text-align: center;
}
@ -66,10 +49,13 @@ h3 { font-size: 110%; }
.page {
background: var(--background);
border: var(--border);
box-shadow: var(--shadow);
position: relative;
padding: 2em 4em;
margin: 0 auto;
margin: 3em auto 3.5em;
border-radius: var(--border-radius);
color: var(--text-col);
text-shadow: var(--text-shadow);
@ -82,9 +68,9 @@ header h1 {
a {
color: inherit;
text-decoration: dotted underline;
text-decoration-thickness: 2px;
}
a:focus {
outline: none;
color: var(--focus-text);
@ -111,7 +97,7 @@ figure > img {
margin: 0;
padding: 0;
position: absolute;
top: 1em;
top: 0.5em;
font-size: 100%;
font-weight: 500;
@ -137,7 +123,6 @@ figure > img {
display: flex;
align-items: flex-start;
flex-flow: row wrap;
margin-top: 0;
margin-bottom: -0.5em;
}
@ -154,7 +139,7 @@ figure > img {
justify-content: center;
}
.buttonbar input {
.bb-choice input {
display: inline;
-webkit-appearance: none;
-moz-appearance: none;
@ -164,27 +149,29 @@ figure > img {
width: 0;
}
.buttonbar label, .bb-links li {
.bb-choice label, .bb-links li {
margin-right: 0.5em;
padding: var(--button-pad);
padding: 0 0.35em;
border-radius: var(--button-corner);
border: 1px solid var(--text-col);
background: var(--button-bg);
border: var(--button-border);
border-radius: var(--button-radius);
text-shadow: none;
}
.buttonbar :focus ~ label, .bb-links li:focus-within {
.bb-choice :focus ~ label, .bb-links li:focus-within {
box-shadow: var(--focus-box);
}
.buttonbar :checked ~ label {
background: var(--button-bg-selected);
border-color: var(--button-border-selected);
.bb-choice :checked ~ label {
color: var(--button-bg);
background: var(--text-col);
}
summary, summary h2 {
summary {
cursor: pointer;
display: inline;
position: relative;
}
summary:focus-within {
@ -195,16 +182,28 @@ summary { list-style: none; }
summary::-webkit-details-marker { display: none; }
summary::after {
display: inline-block;
margin-left: 1.5em;
padding: var(--button-pad);
background: var(--button-bg);
border: var(--button-border);
border-radius: var(--button-radius);
--fg: var(--text-col);
--bg: var(--button-bg);
background: var(--bg);
color: var(--fg);
text-shadow: none;
border: 1px solid var(--fg);
border-radius: var(--button-corner);
position: absolute;
right: 0; top: 0;
padding: 2px 5px;
margin-left: 1ex;
}
summary::after { content: 'show'; }
[open] summary::after { content: 'hide'; }
details summary::after { content: 'show'; }
details[open] summary::after {
content: 'hide';
--fg: var(--button-bg);
--bg: var(--text-col);
}
dt {
@ -233,11 +232,6 @@ p {
hyphens: auto;
}
del {
text-decoration: line-through wavy;
text-decoration-thickness: 2px;
}
.threecol {
columns: 3;
@ -257,19 +251,18 @@ del {
:root {
--gradient:
linear-gradient(135deg,
hsl(42deg, 37%, 20%),
hsl(348deg, 37%, 20%),
hsl(334deg, 42%, 20%),
hsl(234deg, 67%, 18%),
hsl(195deg, 37%, 15%),
hsl(155deg, 32%, 15%)
hsl(42deg, 27%, 25%),
hsl(348deg, 27%, 25%),
hsl(334deg, 32%, 25%),
hsl(234deg, 57%, 23%),
hsl(195deg, 27%, 20%),
hsl(155deg, 22%, 20%)
);
--text-col: hsl(55deg, 60%, 90%);
}
--button-bg-selected: hsla(55deg, 40%, 95%, 20%);
--button-border-selected: 1px solid hsl(55deg, 60%, 90%, 40%);
--button-bg: hsla(0deg, 0%, 0%, 50%);
--button-border: 1px solid hsla(0deg, 0%, 100%, 40%);
body {
--shadow-col: hsl(42deg, 82%, 90%, 20%);
--border-col: black;
}

View File

@ -3,155 +3,93 @@
:root {
--image-size: 200px;
--badge-size: calc(1/4 * var(--image-size));
--gap: 0em;
--gap: 1em;
}
@media (min-width: 1000px) {
.page { max-width: 80%; }
}
.page {
padding: 2em calc(1/4 * var(--image-size));
}
#filters {
margin: 1em 0 2em 0;
}
#filters div {
display: grid;
grid-template-columns: 15% auto;
align-items: baseline;
gap: 0.75em;
grid-gap: 0.5em 0.75em;
margin: 1em 0 2em 0;
}
#filters h3 {
#filters h3, #clear, #singles {
margin: 0;
}
#filters h3 {
#clear, #singles {
font-weight: 400;
font-size: 110%;
}
#filters h3, #clear {
text-align: right;
grid-area: auto / 1;
}
.filterlist {
display: flex;
flex-flow: row wrap;
padding: 0;
font-weight: 500;
font-size: 90%;
gap: 0.5em;
#singles {
text-align: left;
grid-area: auto / 2;
}
.filterlist input {
appearance: none;
}
.filterlist li:not([hidden]) {
display: block;
}
.filterlist li:focus-within {
color: var(--focus-text);
}
.filterlist label {
cursor: pointer;
padding: 0.15em 0.4em;
border-radius: 1000px;
border: 1px solid transparent;
}
.filterlist label::before {
content: url('/style/unchecked.svg');
display: inline-block;
height: 1em;
width: 1em;
vertical-align: -15%;
padding-right: 0.25em;
text-shadow: none;
}
.filterlist :checked + label::before { content: url('/style/checked.svg'); }
.filterlist :checked + label {
background: var(--button-bg);
border: var(--button-border);
}
.filterlist label:not([data-count="1"])::after {
content: attr(data-count);
font-size: 80%;
font-weight: 400;
padding: 0 0.5em;
}
.filterlist [data-count="1"] {
font-size: 85%;
padding-right: 0.8em;
}
.filterlist input {
margin: 0;
}
#filterstuff {
padding: 0;
grid-area: auto / span 2;
display: flex;
justify-content: center;
margin-top: 0;
gap: 2em;
}
#filterstuff li {
list-style: none;
display: inline-block;
padding: var(--button-pad);
border-radius: var(--button-radius);
background: var(--button-bg);
border: var(--button-border);
}
#filterstuff a {
font-weight: 500;
text-decoration: none;
}
#filters-details:not([open])::after {
content: attr(data-filters);
margin-left: 2em;
font-size: 90%;
}
@media (max-width: 80rem) {
#filters div {
grid-template-columns: auto;
}
#filters h3 {
#filters h3, #clear {
text-align: left;
grid-area: unset;
}
#filterstuff {
grid-area: unset;
flex-flow: column;
gap: 0.2em;
}
#filterstuff li {
border-radius: 1em;
}
}
#filters ul {
font-weight: 400;
font-size: 90%;
margin: 0;
border-radius: 0.5em;
border: 1px solid var(--text-col);
overflow: hidden;
background: var(--text-col);
grid-gap: 1px;
}
#filters ul:focus-within {
box-shadow: var(--focus-box);
}
#filters li {
margin: 0;
flex-grow: 1;
}
#filters li:focus-within {
color: var(--focus-text);
}
#filters label {
display: block;
margin: 0;
border-radius: 0;
padding: 0.15em 0.5em;
text-align: center;
border: none;
box-shadow: none;
}
#filters label[data-count]::after {
content: '(' attr(data-count) ')';
font-size: 80%;
padding-left: 0.25em;
}
.grid {
padding: 0;
display: grid;
grid: auto-flow / repeat(auto-fit, var(--image-size));
gap: var(--gap);
grid-template-columns: repeat(auto-fill, var(--image-size));
grid-gap: var(--gap);
justify-content: center;
}
@ -168,18 +106,36 @@
.item:not(.year-marker) {
box-shadow: var(--text-shadow);
outline: var(--border-thickness) solid var(--border-col);
background: hsl(0, 0%, 0%, 50%);
clip-path: polygon(5% 0, 95% 10%, 95% 100%, 5% 90%);
}
.item img {
clip-path: polygon(7% 2%, 93% 12%, 93% 98%, 7% 88%);
border: var(--border-thickness) solid var(--text-col);
border-radius: 0.5em;
background: hsl(340, 45%, 65%);
}
.item:focus-within {
box-shadow: var(--focus-box);
}
figure {
margin: 0;
padding: 0;
}
figcaption .date, figcaption .title {
position: absolute;
width: 100%;
border: 1px solid var(--text-col);
display: block;
text-align: center;
background: hsl(0, 0%, 0%, 75%);
font-size: 80%;
text-shadow: none;
}
figcaption .date { top: -1px; left: -1px; }
figcaption .title { bottom: -1px; left: -1px; }
.date { text-transform: lowercase; }
.year-marker {
/* uncomment to reenable line breaks before year markers */
/* grid-area: auto / 1; */
@ -190,7 +146,7 @@
--gap: 0.2em;
display: grid;
grid-template-columns: repeat(2, calc(50% - 3 * var(--gap)));
gap: var(--gap);
grid-gap: var(--gap);
align-items: center;
justify-content: center;
height: 100%;
@ -207,28 +163,30 @@
}
.item.nsfw::before, .item[data-updated="true"]::after {
height: var(--badge-size);
width: var(--badge-size);
height: var(--size);
width: var(--size);
transform: var(--base-transform);
display: inline-block;
position: absolute;
mix-blend-mode: hard-light;
mix-blend-mode: multiply;
}
.item.nsfw::before {
transform: rotate(15deg);
--size: calc(1/4 * var(--image-size));
--base-transform: rotate(var(--nsfw-sticker-rotate));
content: url(../18_plus_white.svg);
top: 11%;
right: 7%;
z-index: 100;
top: calc(1em + 3px);
right: 3px;
}
.item[data-updated="true"]::after {
transform: rotate(-8deg);
--size: calc(1/4 * var(--image-size));
--base-transform: rotate(-8deg);
content: url(../sparkles.svg);
bottom: 4%;
right: 7%;
bottom: calc(1em + 3px);
right: 3px;
}
footer {
@ -237,6 +195,68 @@ footer {
margin-top: 1em;
}
@media (hover) and (pointer: fine) {
.item:hover .date, .item:hover .title,
.item:hover::before, .item:hover::after {
filter: opacity(20%);
}
@media (prefers-reduced-motion: no-preference) {
figcaption .date, figcaption .title, .item::before, .item::after {
transition-property: filter, transform;
transition-duration: 0.15s;
transition-timing-function: ease-in-out;
}
.item:hover .title {
transform: translate(-20%, 80%) rotateZ(7deg);
}
.item:hover .date {
transform: translate(20%, -80%) rotateZ(7deg);
}
.item:hover::before {
transform: translate(1.5em, -1.5em) var(--base-transform);
}
.item:hover::after {
transform: translate(1.5em, 1.5em) var(--base-transform);
}
}
}
@media (not hover), (pointer: coarse) {
.item:not(.year-marker) {
height: min-content;
}
figcaption .date, figcaption .title {
position: initial;
}
figcaption .date {
border-bottom: none;
}
figcaption .title {
border-top: none;
}
figcaption .date::after {
content: ':';
}
.item a {
display: block;
height: var(--image-size);
}
.item img {
margin-bottom: 0;
}
}
@media (pointer: coarse) {
#filters label {
font-size: 150%;

View File

@ -9,7 +9,6 @@
.page {
width: 37.5em;
border-radius: var(--border-radius);
}
#title::before, #title::after {
@ -31,11 +30,12 @@
}
@media not speech {
@media screen {
.nsfw::after {
content: url(../18_plus_white.svg);
height: 1em;
width: 1em;
transform: rotate(var(--nsfw-sticker-rotate));
mix-blend-mode: hard-light;
margin-left: 0.3em;
}
@ -43,7 +43,7 @@
@media speech {
.nsfw::after {
content: ' (contains adult content)';
content: ' (some nsfw)';
}
}
@ -67,7 +67,7 @@
align-items: center;
justify-content: space-evenly;
padding: 0;
gap: 1.5em;
grid-gap: 1.5em;
font-size: 175%;
}
@ -93,7 +93,7 @@ main {
.list {
font-size: 300%;
grid-template-columns: 100%;
gap: 1em;
grid-gap: 1em;
}
}

View File

@ -20,11 +20,11 @@
"icon text"
"buttons buttons"
/ 1fr 3fr;
gap: 0.5em;
grid-gap: 0.5em;
align-items: center;
min-height: 20vh;
max-width: 30em;
max-width: 60vw;
padding: 1.5em 3em 2em;
background: var(--background);
@ -48,7 +48,6 @@
.dialog-message {
grid-area: text;
justify-self: start;
font-size: 125%;
}
.dialog-buttons {
@ -61,8 +60,8 @@
margin-top: 1em;
}
.dialog-buttons > * {
margin: 0 1em;
.dialog button + button {
margin-left: 1em;
}
.dialog button {
@ -72,18 +71,7 @@
font-family: Muller;
font-weight: 600;
font-size: inherit;
color: black;
position: relative;
cursor: pointer;
}
.dialog button a {
inset: 0;
width: max-content;
text-decoration: none;
}
.dialog .yes {
@ -94,16 +82,6 @@
background: hsl(5deg, 70%, 80%);
}
.dialog p {
text-align: left;
-ms-hyphens: none;
hyphens: none;
}
.dialog strong {
font-weight: 800;
}
@media (pointer: coarse) {
button {
font-size: 150%;

View File

@ -49,22 +49,6 @@
}
.pkmn-nature-down {
color: hsl(200deg, 80%, 80%);
}
.pkmn-nature-up {
color: hsl(340deg, 100%, 87%);
}
th:is(.pkmn-nature-down,.pkmn-nature-up)::after {
vertical-align: super;
font-weight: 500;
}
th.pkmn-nature-down::after { content: ''; }
th.pkmn-nature-up::after { content: '+'; }
.bug {
--type-col: #83c300;

View File

@ -6,14 +6,8 @@
--image-width: 1000px;
}
body {
display: grid;
min-height: 100vh;
}
.page {
max-width: var(--image-width);
align-self: center;
}
#mainfig {
@ -23,11 +17,28 @@ body {
width: min-content;
position: relative;
overflow: hidden;
border: var(--border-thickness) solid var(--border-col);
border: var(--border-thickness) solid var(--text-col);
border-radius: 1em;
box-shadow: var(--text-shadow);
background: hsl(340, 45%, 65%);
}
#mainfig:not(.tiny)::after {
content: 'click for full (' attr(data-width) '×' attr(data-height) ')';
position: absolute;
top: calc(0px - var(--border-thickness));
right: calc(0px - var(--border-thickness));
padding: 0.15em 1.25em 0.15em 0.75em;
font-size: 70%;
font-weight: 700;
background: hsl(0, 0%, 0%, 50%);
border: var(--border-thickness) solid var(--text-col);
border-bottom-left-radius: 0.5em;
}
#mainfig:focus-within {
box-shadow: var(--focus-box);
}
@ -58,7 +69,7 @@ body {
font-weight: 700;
color: hsl(330deg, 100%, 90%);
text-shadow: none;
transform: rotate(-15deg);
transform: rotate(-45deg);
background: hsl(330deg, 40%, 16%);
padding: 0.25em 0.5em;
@ -81,6 +92,20 @@ body {
}
}
/*
.nsfw-label::after {
content: url(../18_plus_white.svg);
display: inline-block;
height: 0.9em; width: 0.9em;
vertical-align: -0.07em;
padding-left: 0.25em;
}
:checked ~ .nsfw-label::after {
content: url(../18_plus.svg);
}
*/
#date { text-transform: lowercase; }
#info {
@ -95,6 +120,9 @@ body {
align-items: baseline;
}
/* 'display: contents' removes things from the accessibility tree
* which is probably only a problem for screen readers?
*/
@media not speech {
.info-section {
display: contents;
@ -102,13 +130,10 @@ body {
}
#info figure {
width: min-content;
margin: 0.25em auto;
}
#info figure img {
max-width: 100%;
}
#info .light-bg {
background: hsl(0deg, 0%, 100%, 75%);
padding: 5px;
@ -118,7 +143,6 @@ body {
#info .floating {
float: right;
margin-left: 0.8em;
max-width: 40%;
}
#info .floating.left {
@ -134,7 +158,7 @@ body {
}
#info h2, #info ul, #info ol, #info p, #info dl, #info details {
margin: 0.35em 0;
margin: 0.35em;
}
#info details > * {
@ -144,7 +168,7 @@ body {
#updates dl {
display: grid;
grid-template-columns: min-content auto;
gap: 0.5em;
grid-gap: 0.5em;
align-items: baseline;
}
@ -182,43 +206,13 @@ footer {
#alts {
margin: 1.5em 0;
text-align: center;
display: grid;
gap: 0.5em;
grid-template-columns: minmax(auto, 10em) auto minmax(auto, 10em);
}
#alts.cat :is(h3, ul) { margin: 0; }
#alts section {
display: contents;
}
.cat :is(h3,ul) { margin: 0; }
#alts h3 {
font-weight: 600;
display: inline;
padding-right: 0.5em;
text-align: right;
grid-area: auto / 1 / auto / auto;
}
#alts ul {
display: inline flex;
grid-area: auto / 2 / auto / auto;
}
.cat ul { justify-content: start; }
#skipAllDiv {
align-self: start;
justify-content: end;
grid-area: 1 / 3 / auto / auto;
}
:is(#tags, #links) ul {
padding: 0;
}
:is(#tags, #links) li {
display: inline;
margin-right: 0.75em;
}
#alts ul { display: inline flex; }

BIN
style/tyranitar.png (Stored with Git LFS)

Binary file not shown.

View File

@ -1,20 +0,0 @@
<?xml version="1.0" encoding="UTF-8" standalone="no"?><!DOCTYPE svg PUBLIC "-//W3C//DTD SVG 1.1//EN" "http://www.w3.org/Graphics/SVG/1.1/DTD/svg11.dtd"><svg width="100%" height="100%" viewBox="0 0 32 32" version="1.1" xmlns="http://www.w3.org/2000/svg" xmlns:xlink="http://www.w3.org/1999/xlink" xml:space="preserve" xmlns:serif="http://www.serif.com/" style="fill-rule:evenodd;clip-rule:evenodd;stroke-linecap:round;stroke-linejoin:round;stroke-miterlimit:1.5;">
<metadata>
<rdf:RDF xmlns:cc="http://web.resource.org/cc/"
xmlns:rdf="http://www.w3.org/1999/02/22-rdf-syntax-ns#"
xmlns:dc = "http://purl.org/dc/elements/1.1/"
>
<rdf:Description rdf:about="">
<dc:title>Mutant Standard emoji 2020.04</dc:title>
</rdf:Description>
<cc:work rdf:about="">
<cc:license rdf:resource="http://creativecommons.org/licenses/by-nc-sa/4.0/"/>
<cc:attributionName>Dzuk</cc:attributionName>
<cc:attributionURL>http://mutant.tech/</cc:attributionURL>
</cc:work>
</rdf:RDF>
</metadata>
<rect id="small_white_square" x="0" y="0" width="32" height="32" style="fill:none;"/><g id="outline"><rect x="12" y="11" width="8" height="10" style="fill:none;stroke:#000;stroke-width:4px;"/></g><g id="emoji"><path d="M20,21l-8,0l0,-2l2,-2l4,0l2,2l0,2Z" style="fill:#b2b2b2;"/><rect x="12" y="11" width="8" height="8" style="fill:#fff;"/></g></svg>

Before

Width:  |  Height:  |  Size: 1.4 KiB