stabilize and parametrize sorting of stuff, get rid of "title"

This commit is contained in:
Mirek Kratochvil 2023-10-15 23:06:59 +02:00 committed by Mirek Kratochvil
parent 53aa481aac
commit 1f2ab58478
9 changed files with 51 additions and 25 deletions

44
Tags.hs
View file

@ -5,7 +5,7 @@ module Tags where
import qualified Data.Aeson.Key as K import qualified Data.Aeson.Key as K
import qualified Data.Aeson.KeyMap as KM import qualified Data.Aeson.KeyMap as KM
import Data.Foldable (traverse_) import Data.Foldable (traverse_)
import Data.List (inits, nub) import Data.List (inits, nub, sortOn)
import Data.List.Extra (groupSort) import Data.List.Extra (groupSort)
import qualified Data.Map as M import qualified Data.Map as M
import Data.String (fromString) import Data.String (fromString)
@ -14,7 +14,7 @@ import qualified Data.Yaml as Y
import Lens.Micro import Lens.Micro
import Lens.Micro.Aeson import Lens.Micro.Aeson
import Lens.Micro.Mtl import Lens.Micro.Mtl
import System.FilePath ((</>), splitDirectories, takeFileName) import System.FilePath ((</>), joinPath, splitDirectories, takeFileName)
import AesonUtils import AesonUtils
import Types import Types
@ -53,7 +53,7 @@ sourceTagMetaFile fp = do
kx = splitTag ks kx = splitTag ks
v v
| Y.String t <- v' = | Y.String t <- v' =
Y.Object $ KM.fromList [("title", Y.String t)] Y.Object $ KM.fromList [("name", Y.String t)]
| Y.Object _ <- v' = v' | Y.Object _ <- v' = v'
| otherwise = | otherwise =
error ("invalid definition of tag " ++ ks ++ " in " ++ fp) error ("invalid definition of tag " ++ ks ++ " in " ++ fp)
@ -69,10 +69,10 @@ sourceTagMetaFile fp = do
-- | Find a good display name for the _last_ hierarchical part of the htag. -- | Find a good display name for the _last_ hierarchical part of the htag.
getTagGroupName :: [String] -> Site String getTagGroupName :: [String] -> Site String
getTagGroupName htag = getTagGroupName htag =
handleEmpty . maybe backup id . (>>= title) . (M.!? htag) <$> use tagMeta handleEmpty . maybe backup id . (>>= name) . (M.!? htag) <$> use tagMeta
where where
title :: Y.Value -> Maybe String name :: Y.Value -> Maybe String
title obj = obj ^? key "title" . _String . to T.unpack name obj = obj ^? key "name" . _String . to T.unpack
backup backup
| null htag = "" | null htag = ""
| null (last htag) = "(unnamed)" | null (last htag) = "(unnamed)"
@ -129,6 +129,21 @@ htagRenderMeta makeLink htag = do
metas) metas)
] ]
data SortKey num
= Negative num
| Stringy String
| Positive num
deriving (Show, Eq, Ord)
toSortKey ident x
| Just i <- x ^? key "meta" . key "order" . _Number =
if i <= 0
then Negative i
else Positive i
| Just s <- x ^? key "meta" . key "order" . _String = Stringy (T.unpack s)
| Just n <- x ^? key "name" . _String = Stringy (T.unpack n)
| otherwise = Stringy ident
-- | A generic helper for rendering metadata for tagged pages. -- | A generic helper for rendering metadata for tagged pages.
genericTaggedPagesRenderMeta :: genericTaggedPagesRenderMeta ::
(FilePath -> Site Y.Value) (FilePath -> Site Y.Value)
@ -136,7 +151,12 @@ genericTaggedPagesRenderMeta ::
-> M.Map [String] [FilePath] -> M.Map [String] [FilePath]
-> Site Y.Value -> Site Y.Value
genericTaggedPagesRenderMeta makePageMeta htag tagmap = genericTaggedPagesRenderMeta makePageMeta htag tagmap =
Y.array <$> traverse makePageMeta (maybe [] id $ tagmap M.!? htag) -- TODO sort page listings here Y.array . map snd . sortOn (uncurry toSortKey) <$>
traverse metaPair (maybe [] id $ tagmap M.!? htag)
where
metaPair x = do
m <- makePageMeta x
pure (x, m)
-- | Render metadata for all precisely tagged pages (not considering the -- | Render metadata for all precisely tagged pages (not considering the
-- inheritance of tags following the hierarchy). -- inheritance of tags following the hierarchy).
@ -163,9 +183,13 @@ htagRenderMetaWithSubtags ::
-> Site Y.Value -> Site Y.Value
htagRenderMetaWithSubtags makeLink extraMeta subtagMeta htag = do htagRenderMetaWithSubtags makeLink extraMeta subtagMeta htag = do
meta <- htagRenderMeta makeLink htag meta <- htagRenderMeta makeLink htag
em <- extraMeta htag
subtags <- subtags <-
filter ((== htag) . init) . filter (not . null) . M.keys <$> use ehtags filter ((== htag) . init) . filter (not . null) . M.keys <$> use ehtags
{- TODO sort tag listings here -} let metaPair x = do
em <- extraMeta htag m <- subtagMeta x
subtagMetas <- Y.array . filter (/= Y.Null) <$> traverse subtagMeta subtags pure (joinPath x, m)
subtagMetas <-
Y.array . filter (/= Y.Null) . map snd . sortOn (uncurry toSortKey) <$>
traverse metaPair subtags
pure $ meta `objMerge` Y.object [("subtags", subtagMetas)] `objMerge` em pure $ meta `objMerge` Y.object [("subtags", subtagMetas)] `objMerge` em

View file

@ -28,7 +28,7 @@ import System.Directory
, doesDirectoryExist , doesDirectoryExist
, getDirectoryContents , getDirectoryContents
) )
import System.FilePath ((</>), takeDirectory, splitDirectories) import System.FilePath ((</>), splitDirectories, takeDirectory)
import Text.Pandoc.Definition import Text.Pandoc.Definition
import qualified Text.Pandoc.Walk import qualified Text.Pandoc.Walk
import Types import Types
@ -132,7 +132,8 @@ sourcePaths fp process = do
| null ds = False | null ds = False
| last ds `elem` notSource = True | last ds `elem` notSource = True
| otherwise = False | otherwise = False
io (getRecursiveContents (pure . ignoreDir . splitDirectories) fp) >>= foldMapM process io (getRecursiveContents (pure . ignoreDir . splitDirectories) fp) >>=
foldMapM process
-- | Given a path to a file, try to make the path writable by making all -- | Given a path to a file, try to make the path writable by making all
-- directories on the path. (Interned from Hakyll.) -- directories on the path. (Interned from Hakyll.)

View file

@ -2,7 +2,7 @@
mount: / mount: /
redirects: redirects:
- also_index - also_index
title: Home name: Home
toc: off toc: off
timestamp: null timestamp: null
--- ---

View file

@ -1,6 +1,6 @@
--- ---
mount: /search mount: /search
title: Search name: Search
template: search.html template: search.html
search: off search: off
toc: off toc: off

View file

@ -439,8 +439,8 @@ makeSearchData :: FilePath -> PageInfo -> Site [Y.Value]
makeSearchData mount pi = do makeSearchData mount pi = do
link <- rootedPageLink mount link <- rootedPageLink mount
text <- io . runIOorExplode $ writePlain plainWriteOpts (pi ^. pageDoc) text <- io . runIOorExplode $ writePlain plainWriteOpts (pi ^. pageDoc)
let title = pi ^? pageMeta . key "title" . _String let name = pi ^? pageMeta . key "name" . _String
-- TODO: unify retrieval of tags -- TODO: unify retrieval of tags?
let tags = let tags =
sort $ pi ^.. pageMeta . key "tags" . values . _String . to T.unpack sort $ pi ^.. pageMeta . key "tags" . values . _String . to T.unpack
tagnames <- traverse (traverse getTagGroupName . inits . splitTag) tags tagnames <- traverse (traverse getTagGroupName . inits . splitTag) tags
@ -450,7 +450,7 @@ makeSearchData mount pi = do
else pure $ else pure $
[ Y.object [ Y.object
[ ("link", fromString link) [ ("link", fromString link)
, ("title", maybe (fromString mount) Y.String title) , ("name", maybe (fromString mount) Y.String name)
, ("tags", tagarray) , ("tags", tagarray)
, ("text", Y.String text) , ("text", Y.String text)
] ]

View file

@ -1,12 +1,13 @@
<head> <head>
<meta charset="UTF-8" /> <meta charset="UTF-8" />
<title> <title>
{{?title}}Page: {{title}}{{/title}} {{^htag}}
{{?name}}Page: {{name}}{{/name}}
{{/htag}}
{{?htag}} {{?htag}}
Category: Category:
{{#htag}} {{#htag}}
{{?tag}} » {{tag}}{{/tag}} {{?name}} » {{name}}{{/name}}
{{^tag}}All pages{{/tag}}
{{/htag}} {{/htag}}
{{/htag}} {{/htag}}
</title> </title>

View file

@ -10,7 +10,7 @@
Categories: Categories:
<ul> <ul>
{{#htags}} {{#htags}}
<li>{{#.}}<a href="{{href}}">{{^tag}}all{{/tag}}{{?tag}} » {{tag}}{{/tag}}{{/.}}</a></li> <li><a href="{{href}}">{{#htag}} » {{name}}{{/htag}}</a></li>
{{/htags}} {{/htags}}
</ul> </ul>
{{/htags}} {{/htags}}

View file

@ -23,7 +23,7 @@
<h3>Pages</h3> <h3>Pages</h3>
<ul> <ul>
{{#pages}} {{#pages}}
<li><a href="{{href}}">{{meta.title}}</a></li> <li><a href="{{href}}">{{meta.name}}</a></li>
{{/pages}} {{/pages}}
</ul> </ul>
{{/pages}} {{/pages}}

View file

@ -15,7 +15,7 @@
<ul> <ul>
{{?pages}} {{?pages}}
{{#pages}} {{#pages}}
<li><a href="{{href}}">{{meta.title}}</a></li> <li><a href="{{href}}">{{meta.name}}</a></li>
{{/pages}} {{/pages}}
{{/pages}} {{/pages}}
{{?subtags}} {{?subtags}}
@ -26,7 +26,7 @@
<ul> <ul>
{{?pages}} {{?pages}}
{{#pages}} {{#pages}}
<li><a href="{{href}}">{{meta.title}}</a></li> <li><a href="{{href}}">{{meta.name}}</a></li>
{{/pages}} {{/pages}}
{{/pages}} {{/pages}}
{{?subtags}} {{?subtags}}
@ -37,7 +37,7 @@
<ul> <ul>
{{?pages}} {{?pages}}
{{#pages}} {{#pages}}
<li><a href="{{href}}">{{meta.title}}</a></li> <li><a href="{{href}}">{{meta.name}}</a></li>
{{/pages}} {{/pages}}
{{/pages}} {{/pages}}
{{?subtags}} {{?subtags}}