summaryrefslogtreecommitdiffstats
path: root/src/Zettel/Render.hs
blob: 28d69237c4cfd7cd8fe41c8e28a0f2a20393697f (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
{-# LANGUAGE OverloadedRecordDot #-}

module Zettel.Render where

import Data.Default (def)
import qualified Data.Map.Strict as Map
import qualified Data.Text as T
import Paths_org_zk (getDataFileName)
import Text.Pandoc.App (applyFilters)
import Text.Pandoc.Builder (HasMeta (..))
import Text.Pandoc.Class (runIOorExplode)
import Text.Pandoc.Definition (Block (..), Inline (..))
import Text.Pandoc.Extensions (Extension (..), disableExtension)
import Text.Pandoc.Filter (Environment (..), Filter (..))
import Text.Pandoc.Options (ReaderOptions (..), WriterOptions (..), getDefaultExtensions, multimarkdownExtensions)
import Text.Pandoc.Scripting (noEngine)
import Text.Pandoc.Templates (WithDefaultPartials (..), compileTemplate)
import Text.Pandoc.Walk (query)
import Text.Pandoc.Writers (writeMarkdown)
import Zettel.Types

zettelIdToLink :: ZettelId -> Inline
zettelIdToLink ident = Link mempty [Str $ "#" <> unZettelId ident] ("/" <> unZettelId ident, "")

renderZettelLinks :: [ZettelId] -> Block
renderZettelLinks =
  BulletList . map (\ident -> [Para [zettelIdToLink ident]])

toInlines :: Text -> [Inline]
toInlines t = intersperse Space . map Str $ T.words t

renderTitleLinks :: Int -> Text -> [ZettelId] -> [Block]
renderTitleLinks level title ids =
  [Header level mempty (toInlines title), renderZettelLinks ids]

newtype MB = MB {unMB :: Bool} deriving (Show, Eq)

instance Semigroup MB where
  MB a <> MB b = MB $ a || b

instance Monoid MB where
  mempty = MB False

checkCitation :: Inline -> MB
checkCitation Cite {} = MB True
checkCitation _ = MB False

renderZettel :: ZettelId -> Zettel -> IO Text
renderZettel _ zettel = do
  templateFile <- getDataFileName "data/markdown.template"
  template <- decodeUtf8 <$> readFileBS templateFile
  Right templ <- runIOorExplode . runWithDefaultPartials $ compileTemplate "" template
  let writeOpts =
        ( def
            { writerTemplate = Just templ,
              writerExtensions = multimarkdownExtensions,
              writerReferenceLinks = True
            }
        )
  runIOorExplode $
    if unMB $ query checkCitation zettel.zettelBody
      then
        let pandoc =
              setMeta "csl" ("/home/ymherklotz/Dropbox/zk/assets/ieee.csl" :: FilePath) $
                setMeta
                  "bibliography"
                  (["/home/ymherklotz/bibliography/references.bib"] :: [FilePath])
                  zettel.zettelBody
         in applyFilters
              noEngine
              ( Environment
                  def {readerExtensions = getDefaultExtensions "org"}
                  writeOpts
                    { writerExtensions =
                        -- Counter-intuitively, you need to disable citation
                        -- support so that the citations are inserted in the
                        -- markdown directly, instead of just referenced.
                        disableExtension Ext_citations writeOpts.writerExtensions
                    }
              )
              [CiteprocFilter]
              ["org"]
              pandoc
              >>= writeMarkdown writeOpts
      else writeMarkdown writeOpts zettel.zettelBody

renderZettelFile :: FilePath -> ZettelId -> Zettel -> IO ()
renderZettelFile dir ident zettel = do
  t <- renderZettel ident zettel
  writeFileText (dir <> "/" <> toString (unZettelId ident <> ".md")) t

renderZettelGraphFile :: FilePath -> ZettelGraph -> IO ()
renderZettelGraphFile fp zg =
  forM_ (Map.assocs (unZettelGraph zg)) $ uncurry (renderZettelFile fp)