gallery/make-pages/Info.hs

460 lines
14 KiB
Haskell
Raw Normal View History

2020-07-07 20:52:01 -04:00
{-# OPTIONS_GHC -Wno-orphans #-}
module Info
2020-11-16 17:30:56 -05:00
(Info (..),
tagsFor, descFor, imagesFor, linksFor, updatesFor, compareFor, sortFor,
2021-08-23 10:30:11 -04:00
Artist (..), Images' (..), Images, Image (..), Desc (..), DescField (..),
Link (..), Update (..),
2020-07-24 19:10:52 -04:00
GalleryInfo (..), GalleryFilters (..), ArtistFilter (..), NsfwFilter (..),
2020-07-18 05:45:32 -04:00
IndexInfo (..),
2020-07-24 19:10:52 -04:00
readArtistFilter, matchArtist, readNsfwFilter, matchNsfw, matchFilters,
2020-08-11 14:29:54 -04:00
NoThumb (..), getThumb, thumbFile, pageFile,
2020-07-07 20:52:01 -04:00
-- ** Reexports
2020-09-25 17:08:44 -04:00
Date (..), Day (..), Text)
2020-07-07 20:52:01 -04:00
where
2020-09-25 17:08:44 -04:00
import Date
2020-07-13 02:33:27 -04:00
import Records
2020-07-15 14:07:51 -04:00
import Control.Applicative
2021-04-16 12:02:17 -04:00
import Control.Monad
2020-08-11 14:29:54 -04:00
import Control.Exception
2021-03-07 19:26:29 -05:00
import Data.Foldable (find)
2020-08-03 20:27:19 -04:00
import Data.Hashable (Hashable)
import Data.HashSet (HashSet)
2020-07-24 19:10:52 -04:00
import qualified Data.HashSet as HashSet
2020-07-15 14:07:51 -04:00
import qualified Data.Map.Strict as Map
2021-04-16 12:02:17 -04:00
import Data.Maybe (isJust, isNothing, fromMaybe, mapMaybe)
2020-11-16 17:30:56 -05:00
import Data.List (nub, sortBy)
2020-07-19 11:55:54 -04:00
import Data.Ord (comparing)
2020-07-16 05:48:09 -04:00
import Data.String (IsString)
2020-07-07 20:52:01 -04:00
import Data.Text (Text)
import qualified Data.Text as Text
2020-07-15 14:07:51 -04:00
import Data.YAML (FromYAML (..), (.:), (.:?), (.!=))
import qualified Data.YAML as YAML
2020-08-11 14:29:54 -04:00
import System.FilePath ((</>), takeBaseName, takeExtension, splitExtension)
2021-08-23 10:30:11 -04:00
import Data.Bifunctor (second)
2020-07-07 20:52:01 -04:00
data Info =
Info {
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,
2020-11-16 17:30:56 -05:00
updates :: ![Update],
-- | if false, don't show updated emblem even if @updates@ is non-empty
showUpdated :: !Bool,
title :: !Text,
artist :: !(Maybe Artist), -- nothing = me, obv
nsfwOnly :: !Bool,
tags :: ![Text],
nsfwTags :: ![Text],
desc :: !Desc,
nsfwDesc :: !Desc,
bg :: !(Maybe Text),
2021-08-23 10:30:11 -04:00
images :: !Images,
thumb' :: !(Maybe FilePath),
links :: ![Link],
extras :: ![FilePath]
2020-07-07 20:52:01 -04:00
}
deriving (Eq, Show)
data Desc =
NoDesc
| TextDesc !Text
| LongDesc ![DescField]
deriving (Eq, Show)
data DescField = DescField {name, text :: !Text}
deriving (Eq, Show)
2020-07-12 22:38:37 -04:00
data Artist =
Artist {
name :: !Text,
url :: !(Maybe Text)
}
deriving (Eq, Show)
2020-07-07 20:52:01 -04:00
data Image =
Image {
2020-07-21 19:48:29 -04:00
label :: !Text,
path :: !FilePath,
download :: !(Maybe FilePath),
nsfw :: !Bool,
warning :: !(Maybe Text)
2020-07-07 20:52:01 -04:00
}
deriving (Eq, Show)
2021-08-23 10:30:11 -04:00
data Images' a =
Uncat [a] -- ^ uncategorised
| Cat [(Text, [a])] -- ^ categorised
deriving (Eq, Show, Functor, Foldable, Traversable)
type Images = Images' Image
2020-07-07 20:52:01 -04:00
data Link =
Link {
2020-07-07 23:27:38 -04:00
title :: !Text,
2020-07-09 15:45:57 -04:00
url :: !Text,
nsfw :: !Bool
2020-07-07 20:52:01 -04:00
}
deriving (Eq, Show)
2020-11-16 17:30:56 -05:00
data Update =
Update {
2021-04-16 12:02:17 -04:00
date :: !Date,
desc :: !Text,
nsfw :: !Bool,
ignoreSort :: !Bool
2020-11-16 17:30:56 -05:00
}
deriving (Eq, Ord, Show)
instance HasField "sfw" Image Bool where getField = not . #nsfw
instance HasField "sfw" Link Bool where getField = not . #nsfw
instance HasField "sfw" Update Bool where getField = not . #nsfw
2020-07-13 02:33:27 -04:00
2021-08-23 10:30:11 -04:00
instance HasField "all" (Images' a) [a] where
getField (Uncat is) = is
getField (Cat cats) = foldMap snd cats
filterImages :: (a -> Bool) -> Images' a -> Images' a
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
2020-07-16 05:47:02 -04:00
instance HasField "anySfw" Info Bool where getField = not . #allNsfw
2020-07-18 05:27:27 -04:00
instance HasField "anyNsfw" Info Bool where getField = not . #allSfw
2020-07-16 05:47:02 -04:00
2020-08-03 13:36:48 -04:00
instance HasField "sfwLinks" Info [Link] where
getField = filter #sfw . #links
instance HasField "nsfwLinks" Info [Link] where
getField = filter #nsfw . #links
2020-11-16 17:30:56 -05:00
instance HasField "sfwUpdates" Info [Update] where
getField = filter #sfw . #updates
instance HasField "nsfwUpdates" Info [Update] where
getField = filter #nsfw . #updates
2020-07-15 14:07:51 -04:00
instance HasField "thumb" Info (Maybe FilePath) where
2021-08-23 10:30:11 -04:00
getField (Info {thumb', images}) =
thumb' <|> #path <$> find #sfw (#all images)
2020-07-15 14:07:51 -04:00
instance HasField "mine" Info Bool where getField = isNothing . #artist
instance HasField "notMine" Info Bool where getField = isJust . #artist
2020-11-16 17:30:56 -05:00
instance HasField "latestDate" Info (Bool -> Date) where
2021-04-16 12:02:17 -04:00
getField info@(Info {date=date}) nsfw =
maximum $ date : mapMaybe relDate (updatesFor nsfw info)
where relDate (Update {date, ignoreSort}) = date <$ guard (not ignoreSort)
2020-09-19 01:51:52 -04:00
2020-11-16 17:30:56 -05:00
instance HasField "latestYear" Info (Bool -> Int) where
getField info nsfw = #year $ #latestDate info nsfw
2020-11-16 17:30:56 -05:00
instance HasField "updated" Info (Bool -> Bool) where
getField (Info {updates, showUpdated}) nsfw = showUpdated && updated
where updated = if nsfw then not $ null updates else any #sfw updates
2020-09-19 01:51:52 -04:00
defDescKey :: Text
defDescKey = "about"
instance Semigroup Desc where
NoDesc <> d2 = d2
d1 <> NoDesc = d1
(TextDesc t1) <> (TextDesc t2) = TextDesc $ t1 <> t2
(LongDesc m1) <> (TextDesc t2) = LongDesc $ m1 <> [DescField defDescKey t2]
(TextDesc t1) <> (LongDesc m2) = LongDesc $ [DescField defDescKey t1] <> m2
2021-03-07 19:26:29 -05:00
(LongDesc m1) <> (LongDesc m2) = LongDesc $ merge m1 m2
merge :: [DescField] -> [DescField] -> [DescField]
merge fs1 fs2 = go fs1 [] fs2 where
go first unused [] = first <> reverse unused
go first unused (x:xs) =
case insert first x of
Just first' -> go first' unused xs
Nothing -> go first (x:unused) xs
insert [] _ = Nothing
insert (x:xs) y =
if #name x == #name y then
Just $ x {text = #text x <> #text y} : xs
else
2021-03-07 19:26:29 -05:00
(x :) <$> insert xs y
instance Monoid Desc where
mempty = NoDesc
mappend = (<>)
instance HasField "exists" Desc Bool where
getField d = d /= NoDesc
descFor :: Bool -> Info -> Desc
descFor nsfw (Info {desc, nsfwDesc}) = if nsfw then desc <> nsfwDesc else desc
2020-08-03 13:36:48 -04:00
tagsFor :: Bool -> Info -> [Text]
tagsFor nsfw i = if nsfw then nub (#tags i <> #nsfwTags i) else #tags i
2020-08-03 13:36:48 -04:00
2021-08-23 10:30:11 -04:00
imagesFor :: Bool -> Info -> Images
2020-08-03 13:36:48 -04:00
imagesFor nsfw = if nsfw then #images else #sfwImages
linksFor :: Bool -> Info -> [Link]
linksFor nsfw = if nsfw then #links else #sfwLinks
2020-11-16 17:30:56 -05:00
updatesFor :: Bool -> Info -> [Update]
updatesFor nsfw = if nsfw then #updates else #sfwUpdates
compareFor :: Bool -> Info -> Info -> Ordering
compareFor nsfw = comparing \i -> (#latestDate i nsfw, #sortEx i, #title i)
sortFor :: Bool -> [Info] -> [Info]
sortFor = sortBy . compareFor
2020-07-19 11:55:54 -04:00
2020-07-07 20:52:01 -04:00
2020-08-11 14:29:54 -04:00
newtype NoThumb = NoThumb FilePath
deriving stock Eq deriving anyclass Exception
instance Show NoThumb where show (NoThumb dir) = "no thumbnail for " ++ dir
getThumb :: FilePath -> Info -> FilePath
getThumb dir =
maybe (throw $ NoThumb dir) (\t -> dir </> thumbFile t) . #thumb
thumbFile :: FilePath -> FilePath
thumbFile = addSuffix "_small"
pageFile :: FilePath -> FilePath
pageFile f
| takeExtension f == ".gif" = f
| otherwise = addSuffix "_med" f
addSuffix :: String -> FilePath -> FilePath
addSuffix suf path =
let (pre, ext) = splitExtension path in
pre ++ suf ++ ext
2020-07-07 20:52:01 -04:00
instance FromYAML Info where
parseYAML = YAML.withMap "info" \m ->
2020-08-04 18:52:39 -04:00
Info <$> m .: "date"
<*> m .:? "sort" .!= ""
2021-03-07 16:09:17 -05:00
<*> (m .:? "updates" >>= updateList)
<*> m .:? "show-updated" .!= True
2020-08-04 18:52:39 -04:00
<*> m .: "title"
<*> m .:? "artist"
<*> m .:? "nsfw-only" .!= False
2020-08-04 18:52:39 -04:00
<*> m .:? "tags" .!= []
<*> m .:? "nsfw-tags" .!= []
<*> m .:? "desc" .!= NoDesc
<*> m .:? "nsfw-desc" .!= NoDesc
<*> m .:? "bg"
2021-08-23 10:30:11 -04:00
<*> m .: "images"
2020-08-04 18:52:39 -04:00
<*> m .:? "thumb"
<*> m .:? "links" .!= []
<*> m .:? "extras" .!= []
2020-07-07 20:52:01 -04:00
2020-07-12 22:38:37 -04:00
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 ->
Artist <$> m .: "name" <*> m .:? "url"
instance FromYAML Desc where
parseYAML y = textDesc y <|> mapDesc y where
textDesc = YAML.withStr "text" $ pure . TextDesc
mapDesc = fmap LongDesc . parseYAML
instance FromYAML DescField where parseYAML = withPair DescField
imageList :: YAML.Node YAML.Pos -> YAML.Parser [Image]
imageList y = pure <$> unlabelledImage y <|> parseYAML y
2020-07-07 20:52:01 -04:00
instance FromYAML Image where
parseYAML y = unlabelledImage y <|> labelled y where
2021-03-07 16:09:17 -05:00
labelled = withPairM \label -> unlabelledImage' (Just label)
unlabelledImage :: YAML.Node YAML.Pos -> YAML.Parser Image
2021-03-07 16:09:17 -05:00
unlabelledImage = unlabelledImage' Nothing
2021-08-23 10:30:11 -04:00
unlabelledImage' :: Maybe Text -> YAML.Node YAML.Pos -> YAML.Parser Image
2021-03-07 16:09:17 -05:00
unlabelledImage' label' y = asStr y <|> asObj y
where
asStr = YAML.withStr "path" \(Text.unpack -> path) ->
2021-03-07 16:09:17 -05:00
let label = fromMaybe (pathToLabel path) label' in
pure $ Image {label, path, download = Nothing,
2020-07-21 19:48:29 -04:00
nsfw = False, warning = Nothing}
asObj = YAML.withMap "image info" \m -> do
2020-07-21 19:48:29 -04:00
path <- m .: "path"
download <- m .:? "download"
nsfw <- m .:? "nsfw" .!= False
warning <- m .:? "warning"
2021-03-07 16:09:17 -05:00
let label = fromMaybe (pathToLabel path) label'
pure $ Image {label, path, download, nsfw, warning}
2021-03-20 06:07:51 -04:00
pathToLabel = Text.pack . gapToSpace . takeBaseName
gapToSpace = map \case '-' -> ' '; '_' -> ' '; c -> c
2020-07-07 20:52:01 -04:00
2021-08-23 10:30:11 -04:00
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
2020-07-07 20:52:01 -04:00
instance FromYAML Link where
2021-03-07 16:09:17 -05:00
parseYAML =
withPairM \title rest -> asStr title rest <|> asObj title rest
2020-07-17 06:29:13 -04:00
where
asStr title = YAML.withStr "url" \url ->
pure $ Link {title, url, nsfw = False}
asObj title = YAML.withMap "link info" \m -> do
url <- m .: "url"
nsfw <- m .:? "nsfw" .!= False
pure $ Link {title, url, nsfw}
2020-07-07 20:52:01 -04:00
2020-11-16 17:30:56 -05:00
2021-03-07 16:09:17 -05:00
updateList :: Maybe (YAML.Node YAML.Pos) -> YAML.Parser [Update]
updateList =
maybe (pure []) $ YAML.withMap "updates" $ traverse asEither . Map.toList
where
asEither (date', rest) = do
date <- parseYAML date'
asDesc date rest <|> asObj date rest
asDesc date = YAML.withStr "desc" \desc ->
2021-04-16 12:02:17 -04:00
pure $ Update {date, desc, nsfw = False, ignoreSort = False}
2021-03-07 16:09:17 -05:00
asObj date = YAML.withMap "update info" \m -> do
2021-04-16 12:02:17 -04:00
desc <- m .: "desc"
nsfw <- m .:? "nsfw" .!= False
ignoreSort <- m .:? "ignore-sort" .!= False
pure $ Update {date, desc, nsfw, ignoreSort}
2020-11-16 17:30:56 -05:00
2020-07-07 20:52:01 -04:00
2020-07-16 05:48:09 -04:00
data GalleryInfo =
GalleryInfo {
2020-07-24 19:17:47 -04:00
title :: !Text,
desc :: !Text,
prefix :: !FilePath,
2020-08-03 20:27:19 -04:00
filters :: !GalleryFilters,
hidden :: !(HashSet Text) -- ^ tags to initially hide
2020-07-16 05:48:09 -04:00
}
deriving (Eq, Show)
2020-11-16 17:30:56 -05:00
instance HasField "nsfw" GalleryInfo Bool where
getField g = #nsfw (#filters g) /= NoNsfw
2020-07-16 05:48:09 -04:00
data GalleryFilters =
GalleryFilters {
2020-07-24 19:17:47 -04:00
nsfw :: !NsfwFilter,
2020-07-24 19:10:52 -04:00
artist :: !ArtistFilter,
2020-08-03 20:27:19 -04:00
require, exclude :: !(HashSet Text)
2020-07-16 05:48:09 -04:00
}
deriving (Eq, Show)
2020-07-24 19:10:52 -04:00
data NsfwFilter = NoNsfw | OnlyNsfw | AllN deriving (Eq, Show)
2020-07-16 05:48:09 -04:00
2020-07-24 19:10:52 -04:00
readNsfwFilter :: (IsString str, Eq str, Alternative f) => str -> f NsfwFilter
readNsfwFilter "no" = pure NoNsfw
readNsfwFilter "only" = pure OnlyNsfw
readNsfwFilter "all" = pure AllN
readNsfwFilter _ = empty
2020-07-16 05:48:09 -04:00
2020-07-24 19:10:52 -04:00
matchNsfw :: NsfwFilter -> Info -> Bool
matchNsfw NoNsfw i = #anySfw i && not (#nsfwOnly i)
2020-07-25 07:58:33 -04:00
matchNsfw OnlyNsfw i = #anyNsfw i
2020-07-24 19:10:52 -04:00
matchNsfw AllN _ = True
2020-07-16 05:48:09 -04:00
2020-07-24 19:10:52 -04:00
instance FromYAML NsfwFilter where
parseYAML = YAML.withStr "nsfw filter" readNsfwFilter
2020-07-16 05:48:09 -04:00
2020-07-24 19:10:52 -04:00
2020-07-31 21:02:26 -04:00
data ArtistFilter = Me | NotMe | AllA deriving (Eq, Show)
2020-07-24 19:10:52 -04:00
readArtistFilter :: (IsString str, Eq str, Alternative f)
=> str -> f ArtistFilter
readArtistFilter "me" = pure Me
readArtistFilter "not-me" = pure NotMe
2020-07-31 21:02:26 -04:00
readArtistFilter "all" = pure AllA
2020-07-24 19:10:52 -04:00
readArtistFilter _ = empty
matchArtist :: ArtistFilter -> Info -> Bool
matchArtist Me = #mine
matchArtist NotMe = #notMine
2020-07-31 21:02:26 -04:00
matchArtist AllA = const True
2020-07-16 05:48:09 -04:00
noFilters :: GalleryFilters
2020-07-24 19:10:52 -04:00
noFilters =
2020-07-31 21:02:26 -04:00
GalleryFilters {nsfw = AllN, artist = AllA, require = [], exclude = []}
2020-07-16 05:48:09 -04:00
matchFilters :: GalleryFilters -> Info -> Bool
2020-07-24 19:10:52 -04:00
matchFilters (GalleryFilters {nsfw, artist, require, exclude}) i =
matchNsfw nsfw i && matchArtist artist i &&
2020-08-03 20:27:19 -04:00
all (\t -> HashSet.member t tags) require &&
all (\t -> not $ HashSet.member t tags) exclude
where tags = HashSet.fromList $ #tags i
2020-07-16 05:48:09 -04:00
instance FromYAML GalleryInfo where
parseYAML = YAML.withMap "gallery info" \m ->
2020-07-16 10:07:28 -04:00
GalleryInfo <$> m .: "title"
2020-07-24 19:17:47 -04:00
<*> m .: "desc"
2020-07-16 10:07:28 -04:00
<*> m .: "prefix"
<*> m .:? "filters" .!= noFilters
2020-08-03 20:27:19 -04:00
<*> m .:? "hidden" .!= mempty
2020-07-16 05:48:09 -04:00
instance FromYAML GalleryFilters where
parseYAML = YAML.withMap "gallery filters" \m ->
2020-07-24 19:10:52 -04:00
GalleryFilters <$> m .:? "nsfw" .!= AllN
2020-07-31 21:02:26 -04:00
<*> m .:? "artist" .!= AllA
2020-07-24 19:10:52 -04:00
<*> m .:? "require" .!= []
<*> m .:? "exclude" .!= []
2020-07-16 05:48:09 -04:00
2020-07-24 19:10:52 -04:00
instance FromYAML ArtistFilter where
parseYAML = YAML.withStr "artist filter" readArtistFilter
2020-07-16 05:48:09 -04:00
2020-07-18 05:45:32 -04:00
data IndexInfo =
IndexInfo {
2020-07-19 06:10:27 -04:00
title :: !Text,
2020-08-11 14:29:54 -04:00
desc :: !Text,
2020-07-18 05:45:32 -04:00
galleries :: ![GalleryInfo],
2020-07-19 06:22:02 -04:00
links :: ![Link],
footer :: !(Maybe Text)
2020-07-18 05:45:32 -04:00
}
deriving Show
instance FromYAML IndexInfo where
parseYAML = YAML.withMap "index info" \m ->
2020-07-19 06:10:27 -04:00
IndexInfo <$> m .: "title"
2020-08-11 14:29:54 -04:00
<*> m .: "desc"
2020-07-19 06:10:27 -04:00
<*> m .:? "galleries" .!= []
2020-07-19 06:22:02 -04:00
<*> m .:? "links" .!= []
<*> m .:? "footer"
2020-07-18 05:45:32 -04:00
2020-07-07 20:52:01 -04:00
data Pair a b = Pair !a !b
instance (FromYAML a, FromYAML b) => FromYAML (Pair a b) where
2020-07-31 21:02:26 -04:00
parseYAML = YAML.withMap "single-pair map" \m ->
case Map.toList m of
[(a, b)] -> Pair <$> parseYAML a <*> parseYAML b
_ -> fail "expected exactly one pair"
2020-07-07 20:52:01 -04:00
2021-03-07 16:09:17 -05:00
withPairM :: (FromYAML a, FromYAML b)
=> (a -> b -> YAML.Parser c)
-> (YAML.Node YAML.Pos -> YAML.Parser c)
withPairM k y = parseYAML y >>= \(Pair a b) -> k a b
withPair :: (FromYAML a, FromYAML b)
=> (a -> b -> c)
-> (YAML.Node YAML.Pos -> YAML.Parser c)
withPair f = withPairM \a b -> pure $ f a b
2020-07-09 15:45:57 -04:00
2020-07-15 05:35:32 -04:00
instance {-# OVERLAPPING #-} FromYAML String where
parseYAML y = Text.unpack <$> parseYAML y
2020-08-03 20:27:19 -04:00
instance (FromYAML a, Eq a, Hashable a) => FromYAML (HashSet a) where
parseYAML y = HashSet.fromList <$> parseYAML y