Compare commits

..

4 commits

3 changed files with 28 additions and 40 deletions

View file

@ -12,7 +12,7 @@ bold ::= '__' text_no_newline '__'
monospace ::= '@' text_content '@' monospace ::= '@' text_content '@'
link ::= module_link | hyperlink | markdown_link link ::= module_link | hyperlink | markdown_link
module_link ::= '"' module_name ( '#' anchor_name )? '"' module_link ::= '"' module_name ( ('#' | '\#') anchor_name )? '"'
hyperlink ::= '<' url ( ' ' link_text )? '>' hyperlink ::= '<' url ( ' ' link_text )? '>'
markdown_link ::= '[' link_text '](' ( url | module_link ) ')' markdown_link ::= '[' link_text '](' ( url | module_link ) ')'

View file

@ -10,7 +10,7 @@ import Control.Monad (mfilter, void)
import Data.Functor (($>)) import Data.Functor (($>))
import Data.Text (Text, intercalate) import Data.Text (Text, intercalate)
import Data.Text qualified as Text import Data.Text qualified as Text
import GHC.Unicode (isAlpha, isAlphaNum, isControl, isPrint, isSpace, isUpper) import GHC.Unicode (isAlphaNum, isControl, isPrint, isSpace, isUpper)
import ParserMonad (Parser, initialParserState) import ParserMonad (Parser, initialParserState)
import Text.Parsec import Text.Parsec
import Text.Parsec qualified as Parsec import Text.Parsec qualified as Parsec
@ -66,9 +66,6 @@ data Token
located :: Parser a -> Parser (SourcePos, a) located :: Parser a -> Parser (SourcePos, a)
located p = (,) <$> getPosition <*> p located p = (,) <$> getPosition <*> p
startPosition :: Parser a -> Parser SourcePos
startPosition = fmap fst . located
tokenise :: [Parser a] -> Parser [(SourcePos, a)] tokenise :: [Parser a] -> Parser [(SourcePos, a)]
tokenise = sequence . map located tokenise = sequence . map located
@ -93,8 +90,8 @@ lexText = go
, spaceToken , spaceToken
, link , link
, labeledLink , labeledLink
, modules , module_
, anchors , anchor
, textElement , textElement
, quotes , quotes
, birdTrack , birdTrack
@ -152,9 +149,6 @@ delimitedSymmetric s t1 t2 = delimited s s t1 t2
eol :: Parser () eol :: Parser ()
eol = void "\n" <|> void "\r\n" <|> Parsec.eof eol = void "\n" <|> void "\r\n" <|> Parsec.eof
anchorHash :: Parser Text
anchorHash = "#" <|> try "\\#"
header1 :: Lexer header1 :: Lexer
header1 = delimitedNoTrailing "= " eol (Header One) header1 = delimitedNoTrailing "= " eol (Header One)
@ -174,11 +168,10 @@ header6 :: Lexer
header6 = delimitedNoTrailing "====== " eol (Header Six) header6 = delimitedNoTrailing "====== " eol (Header Six)
-- #anchors# -- #anchors#
anchors :: Lexer anchor :: Lexer
anchors = anchor = do
tokenise x <- located $ between "#" "#" (Anchor <$> anyUntil "#")
[ between anchorHash anchorHash (Anchor <$> anyUntil anchorHash) pure [x]
]
moduleNames :: Parser Text moduleNames :: Parser Text
@ -192,16 +185,19 @@ identifierChar = satisfy (\c -> isAlphaNum c || c == '_')
-- "Module.Name" -- "Module.Name"
-- "Module.Name#anchor" -- "Module.Name#anchor"
-- "Module.Name\#anchor" -- this has been deprecated for 9 years, thanks Ben -- "Module.Name\#anchor" -- known as "old anchor". this has been deprecated for 9 years, thanks Ben
modules :: Lexer module_ :: Lexer
modules = between (char '"') (char '"') inner module_ = between (char '"') (char '"') inner
where where
inner = do inner = do
module_ <- located $ Module <$> moduleNames m <- located $ Module <$> moduleNames
mAnchor <- optionMaybe (located $ anchorHash *> (Anchor <$> anchorText)) mAnchor <- optionMaybe (located $ anchorHash *> (Anchor <$> anchorText))
pure $ case mAnchor of pure $ case mAnchor of
Just anchor -> [module_, anchor] Just anc -> [m, anc]
Nothing -> [module_] Nothing -> [m]
anchorHash :: Parser Text
anchorHash = "#" <|> try "\\#"
anchorText :: Parser Text anchorText :: Parser Text
anchorText = Text.pack <$> many (satisfy (\c -> c /= '"' && not (isSpace c))) anchorText = Text.pack <$> many (satisfy (\c -> c /= '"' && not (isSpace c)))
@ -227,20 +223,12 @@ link = do
labeledLink :: Lexer labeledLink :: Lexer
labeledLink = do labeledLink = do
pos <- getPosition open <- located $ LabeledLinkOpen <$ "<"
void $ string "<" linkRes <- linkRaw
link' <- linkRaw labelRes <- located $ Token <$> anyUntil ">"
pos7 <- getPosition close <- located $ LabeledLinkClose <$ ">"
label' <- anyUntil $ string ">"
pos8 <- getPosition
void $ ">"
pure $ pure $
(pos, LabeledLinkOpen) open : linkRes <> [ labelRes , close ]
: link'
<> [ (pos7, Token label')
, (pos8, LabeledLinkClose)
]
mathMultiline :: Lexer mathMultiline :: Lexer
mathMultiline = delimited "\\[" "\\]" MathMultilineOpen MathMultilineClose mathMultiline = delimited "\\[" "\\]" MathMultilineOpen MathMultilineClose

View file

@ -19,8 +19,8 @@ main = hspec $ do
describe "minimal" do describe "minimal" do
it "handles unicode" unicode it "handles unicode" unicode
it "escapes" escaping it "escapes" escaping
it "maths" maths it "maths" math
it "anchors" anchors it "anchors" anchor
it "space chars" space it "space chars" space
it "bare string" someString it "bare string" someString
it "emphasis" emphatic it "emphasis" emphatic
@ -84,14 +84,14 @@ labeledLink =
, (1, 35, LabeledLinkClose) , (1, 35, LabeledLinkClose)
] ]
anchors :: Expectation anchor :: Expectation
anchors = anchor =
"#myAnchor#" "#myAnchor#"
`shouldLexTo` [ (1, 1, Anchor "myAnchor") `shouldLexTo` [ (1, 1, Anchor "myAnchor")
] ]
maths :: IO () math :: IO ()
maths = do math = do
"\\[some math\\]" "\\[some math\\]"
`shouldLexTo` [ (1, 1, MathMultilineOpen) `shouldLexTo` [ (1, 1, MathMultilineOpen)
, (1, 3, Token "some math") , (1, 3, Token "some math")