Added picture support
All checks were successful
Haskell CI / build (pull_request) Successful in 2m54s
Haskell CI / test (pull_request) Successful in 2m29s
Haskell CI / fourmolu (pull_request) Successful in 6s
Haskell CI / hlint (pull_request) Successful in 6s

This commit is contained in:
Igor Ranieri 2025-10-05 15:17:57 +02:00
parent ebda9e1d12
commit cae12ef4c0

View file

@ -1,4 +1,5 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
module Lexer ( module Lexer (
Token (..), Token (..),
@ -7,7 +8,7 @@ module Lexer (
) )
where where
import Control.Monad (mfilter, void) import Control.Monad (guard, mfilter, void)
import Data.Char (ord, toLower) import Data.Char (ord, toLower)
import Data.Functor (($>)) import Data.Functor (($>))
import Data.Text (Text, intercalate) import Data.Text (Text, intercalate)
@ -62,6 +63,7 @@ data Token
| Module Text | Module Text
| QuoteOpen | QuoteOpen
| QuoteClose | QuoteClose
| Picture {href :: Text, altText :: Maybe Text}
| Space | Space
| EOF | EOF
deriving (Eq, Show) deriving (Eq, Show)
@ -90,6 +92,7 @@ lexText = go
, escape -- maths go before escape to avoid mismatch , escape -- maths go before escape to avoid mismatch
, headers , headers
, newlineToken , newlineToken
, pictures
, spaceToken , spaceToken
, link , link
, labeledLink , labeledLink
@ -127,6 +130,14 @@ headers =
, header6 , header6
] ]
pictures :: Parser [LocatedToken]
pictures =
choice $
Parsec.try
<$> [ picture
, markdownPicture
]
anyUntil :: Parser a -> Parser Text anyUntil :: Parser a -> Parser Text
anyUntil p = Text.pack <$> manyTill anyChar (lookAhead p) anyUntil p = Text.pack <$> manyTill anyChar (lookAhead p)
@ -177,6 +188,27 @@ anchor = do
x <- located $ between "#" "#" (Anchor <$> anyUntil "#") x <- located $ between "#" "#" (Anchor <$> anyUntil "#")
pure [x] pure [x]
picture :: Lexer
picture = do
void $ string "<<"
pos <- getPosition
href <- anyUntil (string " " <|> string ">>")
altText <- optionMaybe do
void $ many1 space
anyUntil ">>"
void (string ">>")
pure [(pos, Picture{..})]
markdownPicture :: Lexer
markdownPicture = do
void $ string "!["
pos <- getPosition
altText <- optionMaybe $ anyUntil "]("
void $ string "]("
href <- anyUntil ")"
void $ string ")"
pure [(pos, Picture{..})]
moduleNames :: Parser Text moduleNames :: Parser Text
moduleNames = intercalate "." . fmap Text.pack <$> upperId `sepBy1` char '.' moduleNames = intercalate "." . fmap Text.pack <$> upperId `sepBy1` char '.'
@ -286,7 +318,8 @@ other = do
pos <- getPosition pos <- getPosition
c <- takeWhile1_ isUnicodeAlphaNum c <- takeWhile1_ isUnicodeAlphaNum
pure . pure $ (pos, Token c) pure . pure $ (pos, Token c)
where
isUnicodeAlphaNum :: Char -> Bool
isUnicodeAlphaNum c = isPrint c && not (isControl c) && not (isSpace c) isUnicodeAlphaNum c = isPrint c && not (isControl c) && not (isSpace c)
spaceToken :: Lexer spaceToken :: Lexer