From 284c6d3abd4cfa1e0eb91961dadffdb04fdc416a Mon Sep 17 00:00:00 2001 From: Yann Herklotz Date: Fri, 9 Jun 2023 15:18:28 +0100 Subject: Use `.` instead of `>>` in fuction composition --- src/Main.hs | 3 ++- src/Zettel/Math.hs | 10 ++++++++-- src/Zettel/Render.hs | 32 +++++++++++++++++++++----------- 3 files changed, 31 insertions(+), 14 deletions(-) diff --git a/src/Main.hs b/src/Main.hs index 27d16a5..50903d4 100644 --- a/src/Main.hs +++ b/src/Main.hs @@ -358,12 +358,13 @@ main = withStderrLogging $ do graph <- parseZettelKasten (zip [1 ..] fl) (optOrgBibliography zkOpts) - let pipeline = transcludeMdAll >> linkAll >> wrapZettelGraph >> handleBibliography + let pipeline = handleBibliography . wrapZettelGraph . linkAll . transcludeMdAll when (isNothing (optCsl zkOpts)) . warn $ "CSL file not set, using: ieee.csl" when (isNothing (optBibliography zkOpts)) . warn $ "Bibliography file not set, using: references.bib" renderZettelGraphFile + (optVerbose zkOpts > 2) ( fromMaybe "ieee.csl" (optCsl zkOpts) diff --git a/src/Zettel/Math.hs b/src/Zettel/Math.hs index e693e83..49d6420 100644 --- a/src/Zettel/Math.hs +++ b/src/Zettel/Math.hs @@ -8,7 +8,7 @@ -- Portability : POSIX module Zettel.Math where -import Text.Pandoc.Definition (Inline (..)) +import Text.Pandoc.Definition (Inline (..), Block (..)) import Text.Pandoc.Walk (walk) import Zettel.Types @@ -19,5 +19,11 @@ wrapMath = concatMap f f m@(Math _ _) = [RawInline "markdown" "{{< math >}}", m, RawInline "markdown" "{{< /math >}}"] f a = [a] +wrapMathLatex :: Block -> Block +wrapMathLatex r@(RawBlock t b) + | t == "latex" = RawBlock "markdown" $ "{{< math >}}\n" <> b <> "{{< /math >}}" + | otherwise = r +wrapMathLatex r = r + wrapZettelGraph :: ZettelGraph -> ZettelGraph -wrapZettelGraph = walk wrapMath +wrapZettelGraph = walk wrapMathLatex . walk wrapMath diff --git a/src/Zettel/Render.hs b/src/Zettel/Render.hs index 0e7f436..264b7d1 100644 --- a/src/Zettel/Render.hs +++ b/src/Zettel/Render.hs @@ -26,7 +26,7 @@ import Text.Pandoc.Options (ReaderOptions (..), WriterOptions (..), getDefaultEx import Text.Pandoc.Scripting (noEngine) import Text.Pandoc.Templates (WithDefaultPartials (..), compileTemplate) import Text.Pandoc.Walk (query) -import Text.Pandoc.Writers (writeMarkdown) +import Text.Pandoc.Writers (writeMarkdown, writeJSON) import Zettel.Types zettelIdToLink :: ZettelId -> Inline @@ -63,7 +63,9 @@ renderZettel csl bib _ zettel = do let writeOpts = ( def { writerTemplate = Just templ, - writerExtensions = multimarkdownExtensions, + writerExtensions = disableExtension Ext_raw_attribute multimarkdownExtensions + -- enableExtension Ext_intraword_underscores githubMarkdownExtensions + , writerReferenceLinks = True } ) @@ -94,27 +96,35 @@ renderZettel csl bib _ zettel = do >>= writeMarkdown writeOpts else writeMarkdown writeOpts zettel.zettelBody -renderZettelFile :: FilePath -> Maybe FilePath -> FilePath -> ZettelId -> Zettel -> IO () -renderZettelFile csl bib dir ident zettel = do - log $ "Writing " <> T.pack path +renderZettelFile :: Bool -> FilePath -> Maybe FilePath -> FilePath -> ZettelId -> Zettel -> IO () +renderZettelFile json csl bib dir ident zettel = do + log $ "Rendering " <> T.pack path t <- renderZettel csl bib ident zettel writeFileText path t + when json $ do + log $ "Rendering " <> T.pack pathJSON + runIOorExplode (writeJSON def zettel.zettelBody) >>= writeFileText pathJSON where path = dir "zettel" toString (unZettelId ident) <.> "md" + pathJSON = dir "zettel" toString (unZettelId ident) <.> "json" -renderBibFile :: FilePath -> Maybe FilePath -> FilePath -> BibId -> Zettel -> IO () -renderBibFile csl bib dir (BibId ident) zettel = do +renderBibFile :: Bool -> FilePath -> Maybe FilePath -> FilePath -> BibId -> Zettel -> IO () +renderBibFile json csl bib dir (BibId ident) zettel = do log $ "Writing " <> T.pack path t <- renderZettel csl bib (ZettelId ident) zettel writeFileText path t + when json $ do + log $ "Rendering " <> T.pack pathJSON + runIOorExplode (writeJSON def zettel.zettelBody) >>= writeFileText pathJSON where path = dir "bib" toString ident <.> "md" + pathJSON = dir "bib" toString ident <.> "json" -renderZettelGraphFile :: FilePath -> Maybe FilePath -> FilePath -> ZettelGraph -> IO () -renderZettelGraphFile csl bib fp zg = +renderZettelGraphFile :: Bool -> FilePath -> Maybe FilePath -> FilePath -> ZettelGraph -> IO () +renderZettelGraphFile json csl bib fp zg = forM_ (Map.assocs (unZettelGraph zg)) - (uncurry (renderZettelFile csl bib fp)) + (uncurry (renderZettelFile json csl bib fp)) >> forM_ (Map.assocs (zettelGraphBib zg)) - (uncurry (renderBibFile csl bib fp)) + (uncurry (renderBibFile json csl bib fp)) -- cgit