Compare commits

..

2 commits

5 changed files with 37 additions and 83 deletions

View file

@ -1,9 +1,5 @@
module Markdown {-# LANGUAGE OverloadedStrings #-}
( module Markdown.Parser,
module Markdown.Data,
)
where
import Markdown.Data module Markdown () where
import Markdown.Parser
import CMark

View file

@ -1,30 +0,0 @@
{-# LANGUAGE RankNTypes, FlexibleContexts #-}
module Markdown.Data
( MarkDownElement,
MListItem,
Parser,
)
where
import Data.Text
import Text.Parsec
-- modified version of https://github.com/tusharad/markdown-parser
data MarkDownElement
= MHeading Int MarkDownElement
| MParagraph MarkDownElement
| MBold MarkDownElement
| MItalic MarkDownElement
| MBoldItalic MarkDownElement
| MLink MarkDownElement Text
| MLine [MarkDownElement]
| MUnorderedList [MListItem]
| MOrderedList [MListItem]
| Only Text -- Bottom of all types
deriving (Eq, Show)
data MListItem = MListItem MarkDownElement [MarkDownElement]
deriving (Eq, Show)
type Parser v = forall s u m. (Monad m, Stream s m Char) => ParsecT s u m v

View file

@ -1,44 +0,0 @@
{-# LANGUAGE FlexibleContexts #-}
module Markdown.Parser
( Markdown.Parser.lines,
)
where
import Data.Functor (void)
import Data.Text (Text, pack)
import Text.Parsec
-- https://spec.commonmark.org/0.31.2/
-- https://hackage.haskell.org/package/parsec
linebreak ::
(Monad m, Stream s m Char) =>
ParsecT s u m ()
-- 2 newlines due to mark
linebreak = void (newline *> newline)
emptyParse ::
(Monad m, Stream s m Char) =>
ParsecT s u m String
emptyParse = "" <$ notFollowedBy anyChar
line ::
(Monad m, Stream s m Char) =>
ParsecT s u m Text
line = fmap pack $ many $ notFollowedBy linebreak *> anyChar
lines ::
(Monad m, Stream s m Char) =>
ParsecT s u m [Text]
lines = line `sepBy` linebreak
heading ::
(Monad m, Stream s m Char) =>
ParsecT s u m (Int, Text)
heading = do
level <- fmap length $ many1 $ char '#'
text <- line
pure (level, text)
-- TODO: blockquote, single backticks, triple backticks, links, arb HTML

View file

@ -2,3 +2,34 @@ module Restruct where
-- https://docutils.sourceforge.io/rst.html -- https://docutils.sourceforge.io/rst.html
-- https://www.sphinx-doc.org/en/master/usage/restructuredtext/basics.html -- https://www.sphinx-doc.org/en/master/usage/restructuredtext/basics.html
-- https://hackage.haskell.org/package/parsec-3.1.18.0/docs/doc-index-All.html
import Data.Text (Text)
import Data.Void (Void)
import Text.Parsec as P
data RestElement
= RBody RestBody
| RTransition
| -- list of integers is the location in the section heirachy it is, Text is the title
-- NOTE: future me don't bother with proper restext convention do header depth via #n prefix to the title
RSection [Int] Text RestBody
data RestBody
= RParagraph [RInlineText]
| RBulletList Void
| REnumList Void
| RDefinitionList Void
| RFieldList Void
| ROptionList Void
| RLiteralBlock Void
| RLineBlock Void
| RBlockQuote Void
| -- skipping doctest blocks because no I'll just use a literal block thanks
RTable Void
| RExplicit Void
data MarkupModifier = Underline | Bold | Italic
data RInlineText = RInLineText {text :: Text, modifiers :: [MarkupModifier]}

View file

@ -29,13 +29,14 @@ executable psb
-- .hs or .lhs file containing the Main module. -- .hs or .lhs file containing the Main module.
main-is: Main.hs main-is: Main.hs
other-modules: Config Utilities Templates Types IR Markdown Markdown.Data Markdown.Parser Restruct other-modules: Config Utilities Templates Types IR Markdown Restruct
default-extensions: ApplicativeDo DataKinds NamedFieldPuns DerivingVia LambdaCase TypeApplications DeriveGeneric default-extensions: ApplicativeDo DataKinds NamedFieldPuns DerivingVia LambdaCase TypeApplications DeriveGeneric
-- Other library packages from which modules are imported. -- Other library packages from which modules are imported.
-- https://hackage.haskell.org/package/texmath -- https://hackage.haskell.org/package/texmath
build-depends: base >=4.17.2.1, mustache >=2.4.2, pandoc >=3.2.1, shake >= 0.19.8, deriving-aeson >= 0.2.9, aeson, text, time, unordered-containers, yaml, parsec >= 3.1.18.0, typst >= 0.6.1, typst-symbols >= 0.1.7 -- cmark is pinned because I don't want to touch it unless I rewrite to my own code
build-depends: base >=4.17.2.1, mustache >=2.4.2, pandoc >=3.2.1, shake >= 0.19.8, deriving-aeson >= 0.2.9, aeson, text, time, unordered-containers, yaml, parsec >= 3.1.18.0, typst >= 0.6.1, typst-symbols >= 0.1.7, cmark == 0.6.1
-- Directories containing source files. -- Directories containing source files.
hs-source-dirs: app hs-source-dirs: app