Skip to content

Commit

Permalink
Deal with duplicate inline (and meta) tags
Browse files Browse the repository at this point in the history
  • Loading branch information
srid committed Sep 7, 2020
1 parent de5fac5 commit 7556989
Showing 1 changed file with 8 additions and 4 deletions.
12 changes: 8 additions & 4 deletions neuron/src/lib/Neuron/Zettelkasten/Zettel/Parser.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,7 +9,9 @@
module Neuron.Zettelkasten.Zettel.Parser where

import Control.Monad.Writer
import Data.List (nub)
import Data.Some
import Data.TagTree (Tag)
import qualified Data.Text as T
import Data.Time.DateMayTime (mkDateMayTime)
import Neuron.Reader.Type
Expand Down Expand Up @@ -48,10 +50,8 @@ parseZettel format zreader fn zid s = do
ZettelCustomID _ -> Meta.date =<< meta
unlisted = fromMaybe False $ Meta.unlisted =<< meta
(queries, errors) = runWriter $ extractQueries doc
queryTags = flip mapMaybe queries $ \case
Some (ZettelQuery_TagZettel tag) -> Just tag
_ -> Nothing
tags = metaTags <> queryTags -- TODO: Use Set
queryTags = getInlineTag `mapMaybe` queries
tags = nub $ metaTags <> queryTags
in Right $ Zettel zid format fn title titleInBody tags date unlisted queries errors doc
where
-- Extract all (valid) queries from the Pandoc document
Expand All @@ -65,6 +65,10 @@ parseZettel format zreader fn zid s = do
pure Nothing
Right v ->
pure v
getInlineTag :: Some ZettelQuery -> Maybe Tag
getInlineTag = \case
Some (ZettelQuery_TagZettel tag) -> Just tag
_ -> Nothing
takeInitial =
(<> " ...") . T.take 18

Expand Down

0 comments on commit 7556989

Please sign in to comment.