summaryrefslogtreecommitdiffstats
path: root/src/Zettel/Parse.hs
blob: d6d8aa9d4cacc67ce98db12dc948dc67923f783b (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
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
module Zettel.Parse where

import Data.Default (def)
import qualified Data.Map.Strict as Map
import qualified Data.Text as T
import Text.Pandoc.Builder (toMetaValue)
import Text.Pandoc.Chunks (Chunk (..), ChunkedDoc (..), splitIntoChunks)
import Text.Pandoc.Class (runIOorExplode)
import Text.Pandoc.Definition (Block (..), Inline (..), Meta (..), MetaValue (..), Pandoc (..))
import Text.Pandoc.Readers (readOrg)
import Text.Pandoc.Shared (stringify)
import Text.Pandoc.Walk (query, walk)
import Zettel.Types

decode :: ByteString -> Text
decode = decodeUtf8

removeHeadings :: Block -> Block
removeHeadings Header {} = Plain []
removeHeadings a = a

removeDiv :: [Block] -> [Block]
removeDiv = concatMap removeDiv'
  where
    removeDiv' (Div _ b') = b'
    removeDiv' a = [a]

queryHeaderMetaData :: [Block] -> [(Text, MetaValue)]
queryHeaderMetaData = query headingAttr
  where
    headingAttr (Header _ (_, _, l) i) =
      map (bimap exportDate MetaString) l
        <> [ ("title", MetaInlines i),
             ("author", MetaInlines [Str "Yann", Space, Str "Herklotz"])
           ]
    headingAttr _ = []
    exportDate s
      | s == "export_date" = "date"
      | otherwise = s

metaToString :: MetaValue -> Maybe Text
metaToString (MetaString t) = Just t
metaToString _ = Nothing

metaToInlines :: MetaValue -> Maybe [Inline]
metaToInlines (MetaInlines t) = Just t
metaToInlines _ = Nothing

lookupString :: Text -> Meta -> Maybe Text
lookupString t m = Map.lookup t (unMeta m) >>= metaToString

lookupInlines :: Text -> Meta -> Maybe [Inline]
lookupInlines t m = Map.lookup t (unMeta m) >>= metaToInlines

removeSpan :: [Inline] -> [Inline]
removeSpan = concatMap removeSpan'
  where
    removeSpan' (Span _ _) = []
    removeSpan' a = [a]

removeMathNL :: Inline -> Inline
removeMathNL (Math mt t) = Math mt . fold $ T.lines t
removeMathNL a = a

separateTitleTags :: [Inline] -> ([Inline], [ZettelTag])
separateTitleTags title =
  (walk removeSpan $ filter (not . isTagSpan) title, map (ZettelTag . stringify) $ filter isTagSpan title)
  where
    isTagSpan (Span (_, l, _) _) = "tag" `elem` l
    isTagSpan _ = False

parseDate :: Text -> Maybe Text
parseDate t
  | T.null t = Just t
  | T.head t == '[' = viaNonEmpty head . T.words $ T.tail t
  | otherwise = Just t

parseDateVal :: MetaValue -> Maybe MetaValue
parseDateVal v = MetaString <$> (metaToString v >>= parseDate)

zettelMetaFromMeta :: [ZettelTag] -> Meta -> ZettelMetadata
zettelMetaFromMeta t m =
  ZettelMetadata
    (lookupString "date" m)
    (lookupString "modified" m)
    t
    []

pandocFromChunk :: Chunk -> Pandoc
pandocFromChunk c =
  walk removeMathNL
    . walk removeDiv
    . walk removeHeadings
    . Pandoc
      (Meta (fromList (("custom_id", MetaString (chunkId c)) : headingMeta)))
    $ chunkContents c
  where
    headingMeta = queryHeaderMetaData $ chunkContents c

zettelFromPandoc :: Pandoc -> (ZettelId, Zettel)
zettelFromPandoc p@(Pandoc attr _) =
  (ZettelId ident, Zettel title (zettelMetaFromMeta tags attr) p)
  where
    ident = fromMaybe "" $ lookupString "custom_id" attr
    (title, tags) = maybe ([], []) separateTitleTags $ lookupInlines "title" attr

initNode :: Zettel -> ZettelNode
initNode zettel = ZettelNode zettel cempty cempty

updatePandocAttr :: Pandoc -> Pandoc
updatePandocAttr (Pandoc attr b) =
  Pandoc
    ( Meta
        ( Map.insert
            "tags"
            tags
            . Map.update
              (fmap (MetaInlines . fst . separateTitleTags) . metaToInlines)
              "title"
            . Map.update
              parseDateVal
              "modified"
            . Map.update parseDateVal "date"
            $ unMeta attr
        )
    )
    b
  where
    tags =
      toMetaValue . map unZettelTag $
        maybe [] (snd . separateTitleTags) $
          lookupInlines "title" attr

parseZettelKasten :: [FilePath] -> IO ZettelGraph
parseZettelKasten fl = do
  fs <- mapM readFileBS fl
  orgFiles <- mapM (runIOorExplode . readOrg def . decode) fs
  let splitChunks = map (splitIntoChunks "%i.md" False Nothing 15) orgFiles
  let pandocList = map (updatePandocAttr . pandocFromChunk) $ concatMap chunkedChunks splitChunks
  return . ZettelGraph . fromList $ map (second initNode . zettelFromPandoc) pandocList