Setup CI
All checks were successful
Haskell CI / build (pull_request) Successful in 3m13s
Haskell CI / test (pull_request) Successful in 2m13s
Haskell CI / fourmolu (pull_request) Successful in 6s
Haskell CI / hlint (pull_request) Successful in 5s

This commit is contained in:
Igor Ranieri 2025-09-27 07:51:09 +00:00
parent f1cb583d0f
commit 7d561cf329
9 changed files with 508 additions and 325 deletions

View file

@ -1,2 +0,0 @@
runs-on: self-hosted

View file

@ -0,0 +1,99 @@
name: Haskell CI
on:
pull_request:
branches:
- dev
- main
push:
branches:
- main
jobs:
build:
runs-on: docker
container:
image: elland/haddock2:latest
steps:
- name: Checkout code
uses: actions/checkout@v4
- name: Check versions
run: |
ghc --version
cabal --version
node --version
- name: Cache Cabal packages
uses: actions/cache@v4
with:
path: |
~/.cabal/packages
~/.cabal/store
dist-newstyle
key: ${{ runner.os }}-haskell-9.10-cabal-${{ hashFiles('**/*.cabal', '**/cabal.project') }}
restore-keys: |
${{ runner.os }}-haskell-9.10-cabal-
- name: Update Cabal package index
run: cabal update
- name: Configure project
run: cabal configure --enable-tests --enable-benchmarks
- name: Build dependencies
run: cabal build --only-dependencies --enable-tests --enable-benchmarks
- name: Build project
run: cabal build --enable-tests --enable-benchmarks
- name: Run documentation build
run: cabal haddock
test:
runs-on: docker
container:
image: elland/haddock2:latest
needs: build
steps:
- name: Checkout code
uses: actions/checkout@v4
- name: Cache Cabal packages
uses: actions/cache@v4
with:
path: |
~/.cabal/packages
~/.cabal/store
dist-newstyle
key: ${{ runner.os }}-haskell-9.10-cabal-${{ hashFiles('**/*.cabal', '**/cabal.project') }}
restore-keys: |
${{ runner.os }}-haskell-9.10-cabal-
- name: Update Cabal package index
run: cabal update
- name: Configure project
run: cabal configure --enable-tests --enable-benchmarks
- name: Build dependencies
run: cabal build --only-dependencies --enable-tests --enable-benchmarks
- name: Build project
run: cabal build --enable-tests --enable-benchmarks
- name: Run tests
run: cabal test --test-show-details=direct
fourmolu:
runs-on: docker
container:
image: elland/haddock2:latest
needs: build
steps:
- name: Checkout code
uses: actions/checkout@v4
- name: Run fourmolu
run: |
find src test app -name "*.hs" -exec fourmolu --check-idempotence {} \; 2>/dev/null || true
find src test app -name "*.hs" -exec fourmolu --mode check {} \;
hlint:
runs-on: docker
container:
image: elland/haddock2:latest
needs: build
steps:
- name: Checkout code
uses: actions/checkout@v4
- name: Run hlint
run: |
if [ -d src ]; then hlint src/; fi
if [ -d test ]; then hlint test/; fi
if [ -d app ]; then hlint app/; fi

36
Dockerfile Normal file
View file

@ -0,0 +1,36 @@
FROM haskell:9.10.2-bullseye AS builder
RUN apt-get update && apt-get install -y curl git && rm -rf /var/lib/apt/lists/*
RUN curl -fsSL https://deb.nodesource.com/setup_22.x | bash - && \
apt-get install -y nodejs && \
rm -rf /var/lib/apt/lists/*
RUN cabal update && \
cabal install --install-method=copy --installdir=/usr/local/bin \
fourmolu hlint cabal-gild
WORKDIR /workspace
FROM haskell:9.10.2-bullseye
RUN apt-get update && apt-get install -y \
libgmp10 \
curl \
&& rm -rf /var/lib/apt/lists/*
RUN curl -fsSL https://deb.nodesource.com/setup_22.x | bash - && \
apt-get install -y nodejs && \
rm -rf /var/lib/apt/lists/*
RUN cabal update
COPY --from=builder /usr/local/bin/cabal /usr/local/bin/
COPY --from=builder /usr/local/bin/fourmolu /usr/local/bin/
COPY --from=builder /usr/local/bin/hlint /usr/local/bin/
COPY --from=builder /usr/local/bin/cabal-gild /usr/local/bin/
WORKDIR /workspace
CMD [ "bash" ]

44
Makefile Normal file
View file

@ -0,0 +1,44 @@
.PHONY: help
help: ## Show this help
@grep -E '^[a-zA-Z_-]+:.*?## .*$$' $(MAKEFILE_LIST) | sort | awk 'BEGIN {FS = ":.*?## "}; {printf "\033[36m%-30s\033[0m %s\n", $$1, $$2}'
.PHONY: build
build: ## Build the project
cabal build
.PHONY: test
test: ## Run tests
cabal test --test-show-details=direct
.PHONY: clean
clean: ## Clean build artifacts
cabal clean
.PHONY: fourmolu
fourmolu: ## Format Haskell code
find . -type f -name "*.hs" ! -path "./dist-newstyle/*" -exec fourmolu -i {} +
.PHONY: fourmolu-check
fourmolu-check: ## Check if code is formatted
find . -type f -name "*.hs" ! -path "./dist-newstyle/*" -exec fourmolu --mode check {} \;
.PHONY: lint
lint: ## Run hlint
hlint src test app
.PHONY: cabal-gild
cabal-gild: ## Format cabal file
cabal-gild --io=haddock2.cabal
.PHONY: format
format: fourmolu cabal-gild ## Run all formatters
.PHONY: check
check: fourmolu-check lint ## Run all checks (CI-style)
.PHONY: ci
ci: build test check ## Run full CI pipeline locally
.PHONY: docs
docs: ## Generate documentation
cabal haddock --haddock-hyperlink-source

View file

@ -46,10 +46,10 @@ test-suite haddock2-test
type: exitcode-stdio-1.0 type: exitcode-stdio-1.0
main-is: Spec.hs main-is: Spec.hs
build-depends: build-depends:
parsec ^>=3.1.18.0,
base >=4.20.1.0, base >=4.20.1.0,
haddock2:{haddock2-lib}, haddock2:{haddock2-lib},
hspec ^>=2.11.0, hspec ^>=2.11.0,
parsec ^>=3.1.18.0,
text ^>=2.1.2, text ^>=2.1.2,
hs-source-dirs: test hs-source-dirs: test

View file

@ -1,10 +1,11 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
module Lexer ( module Lexer (
Token (..), Token (..),
lexer, lexer,
emphasis, emphasis,
) where )
where
import Control.Monad (mfilter, void) import Control.Monad (mfilter, void)
import Data.Functor (($>)) import Data.Functor (($>))
@ -17,134 +18,135 @@ import Text.Parsec qualified as Parsec
import Text.Parsec.Pos (updatePosChar) import Text.Parsec.Pos (updatePosChar)
type Located a = (SourcePos, a) type Located a = (SourcePos, a)
type LocatedToken = (SourcePos, Token) type LocatedToken = (SourcePos, Token)
type Lexer = Parser [LocatedToken] type Lexer = Parser [LocatedToken]
data Level data Level
= One = One
| Two | Two
| Three | Three
| Four | Four
| Five | Five
| Six | Six
deriving (Eq, Show) deriving (Eq, Show)
data Token data Token
= Token Text = Token Text
| Anchor Text | Anchor Text
| BirdTrack | BirdTrack
| BoldOpen | BoldOpen
| BoldClose | BoldClose
| Escape | Escape
| EmphasisOpen | EmphasisOpen
| EmphasisClose | EmphasisClose
| Header Level | Header Level
| MonospaceOpen | MonospaceOpen
| MonospaceClose | MonospaceClose
| Newline | Newline
| LinkOpen | LinkOpen
| LinkClose | LinkClose
| LabeledLinkOpen | LabeledLinkOpen
| LabeledLinkClose | LabeledLinkClose
| ParenOpen | ParenOpen
| ParenClose | ParenClose
| BracketOpen | BracketOpen
| BracketClose | BracketClose
| MathInlineOpen | MathInlineOpen
| MathInlineClose | MathInlineClose
| MathMultilineOpen | MathMultilineOpen
| MathMultilineClose | MathMultilineClose
| NumericEntity Int | NumericEntity Int
| Module Text | Module Text
| QuoteOpen | QuoteOpen
| QuoteClose | QuoteClose
| Space | Space
| EOF | EOF
deriving (Eq, Show) deriving (Eq, Show)
located :: Parser a -> Parser (SourcePos, a) located :: Parser a -> Parser (SourcePos, a)
located p = (,) <$> getPosition <*> p located p = (,) <$> getPosition <*> p
tokenise :: [Parser a] -> Parser [(SourcePos, a)] tokenise :: [Parser a] -> Parser [(SourcePos, a)]
tokenise = sequence . map located tokenise = mapM located
lexer :: String -> Either ParseError [LocatedToken] lexer :: String -> Either ParseError [LocatedToken]
lexer = Parsec.runParser lexText initialParserState "input" . Text.pack lexer = Parsec.runParser lexText initialParserState "input" . Text.pack
lexText :: Parser [LocatedToken] lexText :: Parser [LocatedToken]
lexText = go lexText = go
where where
go = do go = do
Parsec.optionMaybe Parsec.eof >>= \case Parsec.optionMaybe Parsec.eof >>= \case
Just _ -> pure [] Just _ -> pure []
Nothing -> do Nothing -> do
toks <- toks <-
choice $ choice $
Parsec.try Parsec.try
<$> [ mathMultiline <$> [ mathMultiline
, mathInline , mathInline
, escape -- maths go before escape to avoid mismatch , escape -- maths go before escape to avoid mismatch
, headers , headers
, newlineToken , newlineToken
, spaceToken , spaceToken
, link , link
, labeledLink , labeledLink
, module_ , module_
, anchor , anchor
, textElement , textElement
, quotes , quotes
, birdTrack , birdTrack
, other , other
] ]
rest <- go rest <- go
pure (toks <> rest) pure (toks <> rest)
-- Tokens -- Tokens
textElement :: Parser [LocatedToken] textElement :: Parser [LocatedToken]
textElement = textElement =
choice $ choice $
Parsec.try Parsec.try
<$> [ emphasis <$> [ emphasis
, bold , bold
, monospace , monospace
] ]
headers :: Parser [LocatedToken] headers :: Parser [LocatedToken]
headers = headers =
choice $ choice $
Parsec.try Parsec.try
<$> [ header1 <$> [ header1
, header2 , header2
, header3 , header3
, header4 , header4
, header5 , header5
, header6 , header6
] ]
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)
delimitedAsTuple :: Parser open -> Parser close -> Parser (Located open, LocatedToken, Located close) delimitedAsTuple :: Parser open -> Parser close -> Parser (Located open, LocatedToken, Located close)
delimitedAsTuple openP closeP = delimitedAsTuple openP closeP =
(,,) (,,)
<$> located openP <$> located openP
<*> located (Token <$> anyUntil closeP) <*> located (Token <$> anyUntil closeP)
<*> located closeP <*> located closeP
delimited :: Parser open -> Parser close -> Token -> Token -> Parser [LocatedToken] delimited :: Parser open -> Parser close -> Token -> Token -> Parser [LocatedToken]
delimited openP closeP openTok closeTok = asList <$> delimitedAsTuple (openTok <$ openP) (closeTok <$ closeP) delimited openP closeP openTok closeTok = asList <$> delimitedAsTuple (openTok <$ openP) (closeTok <$ closeP)
where where
asList (a, tok, b) = [a, tok, b] asList (a, tok, b) = [a, tok, b]
delimitedNoTrailing :: Parser open -> Parser close -> Token -> Parser [LocatedToken] delimitedNoTrailing :: Parser open -> Parser close -> Token -> Parser [LocatedToken]
delimitedNoTrailing openP closeP openTok = asList <$> delimitedAsTuple (openTok <$ openP) (void closeP) delimitedNoTrailing openP closeP openTok = asList <$> delimitedAsTuple (openTok <$ openP) (void closeP)
where where
asList (a, tok, _) = [a, tok] asList (a, tok, _) = [a, tok]
delimitedSymmetric :: Parser a -> Token -> Token -> Parser [LocatedToken] delimitedSymmetric :: Parser a -> Token -> Token -> Parser [LocatedToken]
delimitedSymmetric s t1 t2 = delimited s s t1 t2 delimitedSymmetric s = delimited s s
eol :: Parser () eol :: Parser ()
eol = void "\n" <|> void "\r\n" <|> Parsec.eof eol = void "\n" <|> void "\r\n" <|> Parsec.eof
@ -170,9 +172,8 @@ header6 = delimitedNoTrailing "====== " eol (Header Six)
-- #anchors# -- #anchors#
anchor :: Lexer anchor :: Lexer
anchor = do anchor = do
x <- located $ between "#" "#" (Anchor <$> anyUntil "#") x <- located $ between "#" "#" (Anchor <$> anyUntil "#")
pure [x] pure [x]
moduleNames :: Parser Text moduleNames :: Parser Text
moduleNames = intercalate "." . fmap Text.pack <$> upperId `sepBy1` char '.' moduleNames = intercalate "." . fmap Text.pack <$> upperId `sepBy1` char '.'
@ -188,47 +189,47 @@ identifierChar = satisfy (\c -> isAlphaNum c || c == '_')
-- "Module.Name\#anchor" -- known as "old 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
module_ :: Lexer module_ :: Lexer
module_ = between (char '"') (char '"') inner module_ = between (char '"') (char '"') inner
where where
inner = do inner = do
m <- 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 anc -> [m, anc] Just anc -> [m, anc]
Nothing -> [m] Nothing -> [m]
anchorHash :: Parser Text anchorHash :: Parser Text
anchorHash = "#" <|> try "\\#" 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)))
linkRaw :: Lexer linkRaw :: Lexer
linkRaw = linkRaw =
tokenise tokenise
[ BracketOpen <$ "[" [ BracketOpen <$ "["
, Token <$> anyUntil "]" , Token <$> anyUntil "]"
, BracketClose <$ "]" , BracketClose <$ "]"
, ParenOpen <$ "(" , ParenOpen <$ "("
, Token <$> anyUntil ")" , Token <$> anyUntil ")"
, ParenClose <$ ")" , ParenClose <$ ")"
] ]
link :: Lexer link :: Lexer
link = do link = do
pos <- getPosition pos <- getPosition
l <- linkRaw l <- linkRaw
-- register the position of the last token -- register the position of the last token
pos' <- flip incSourceColumn (-1) <$> getPosition pos' <- flip incSourceColumn (-1) <$> getPosition
pure $ (pos, LinkOpen) : l <> [(pos', LinkClose)] pure $ (pos, LinkOpen) : l <> [(pos', LinkClose)]
labeledLink :: Lexer labeledLink :: Lexer
labeledLink = do labeledLink = do
open <- located $ LabeledLinkOpen <$ "<" open <- located $ LabeledLinkOpen <$ "<"
linkRes <- linkRaw linkRes <- linkRaw
labelRes <- located $ Token <$> anyUntil ">" labelRes <- located $ Token <$> anyUntil ">"
close <- located $ LabeledLinkClose <$ ">" close <- located $ LabeledLinkClose <$ ">"
pure $ pure $
open : linkRes <> [ labelRes , close ] open : linkRes <> [labelRes, close]
mathMultiline :: Lexer mathMultiline :: Lexer
mathMultiline = delimited "\\[" "\\]" MathMultilineOpen MathMultilineClose mathMultiline = delimited "\\[" "\\]" MathMultilineOpen MathMultilineClose
@ -256,23 +257,23 @@ monospace = delimitedSymmetric "@" MonospaceOpen MonospaceClose
other :: Lexer other :: Lexer
other = do other = do
pos <- getPosition pos <- getPosition
c <- takeWhile1_ isUnicodeAlphaNum c <- takeWhile1_ isUnicodeAlphaNum
pure . pure $ (pos, Token c) pure . pure $ (pos, Token c)
where where
isUnicodeAlphaNum c = isPrint c && not (isControl c) && not (isSpace c) isUnicodeAlphaNum c = isPrint c && not (isControl c) && not (isSpace c)
spaceToken :: Lexer spaceToken :: Lexer
spaceToken = do spaceToken = do
pos <- getPosition pos <- getPosition
_ <- many1 (char ' ') _ <- many1 (char ' ')
pure . pure $ (pos, Space) pure . pure $ (pos, Space)
newlineToken :: Lexer newlineToken :: Lexer
newlineToken = do newlineToken = do
pos <- getPosition pos <- getPosition
_ <- newline _ <- newline
pure . pure $ (pos, Newline) pure . pure $ (pos, Newline)
------- -------
-- Helpers -- Helpers
@ -281,11 +282,11 @@ newlineToken = do
-- | Like `takeWhile`, but unconditionally take escaped characters. -- | Like `takeWhile`, but unconditionally take escaped characters.
takeWhile_ :: (Char -> Bool) -> Parser Text takeWhile_ :: (Char -> Bool) -> Parser Text
takeWhile_ p = scan p_ False takeWhile_ p = scan p_ False
where where
p_ escaped c p_ escaped c
| escaped = Just False | escaped = Just False
| not $ p c = Nothing | not $ p c = Nothing
| otherwise = Just (c == '\\') | otherwise = Just (c == '\\')
-- | Like 'takeWhile1', but unconditionally take escaped characters. -- | Like 'takeWhile1', but unconditionally take escaped characters.
takeWhile1_ :: (Char -> Bool) -> Parser Text takeWhile1_ :: (Char -> Bool) -> Parser Text
@ -295,19 +296,20 @@ takeWhile1_ = mfilter (not . Text.null) . takeWhile_
function returns true. function returns true.
-} -}
scan :: scan ::
-- | scan function -- | scan function
(state -> Char -> Maybe state) -> (state -> Char -> Maybe state) ->
-- | initial state -- | initial state
state -> state ->
Parser Text Parser Text
scan f initState = do scan f initState = do
parserState@State{stateInput = input, statePos = pos} <- Parsec.getParserState parserState@State{stateInput = input, statePos = pos} <- Parsec.getParserState
(remaining, finalPos, ct) <- go input initState pos 0
let newState = parserState{stateInput = remaining, statePos = finalPos} (remaining, finalPos, ct) <- go input initState pos 0
Parsec.setParserState newState $> Text.take ct input let newState = parserState{stateInput = remaining, statePos = finalPos}
where Parsec.setParserState newState $> Text.take ct input
go !input' !st !posAccum !count' = case Text.uncons input' of where
Nothing -> pure (input', posAccum, count') go !input' !st !posAccum !count' = case Text.uncons input' of
Just (char', input'') -> case f st char' of Nothing -> pure (input', posAccum, count')
Nothing -> pure (input', posAccum, count') Just (char', input'') -> case f st char' of
Just st' -> go input'' st' (updatePosChar posAccum char') (count' + 1) Nothing -> pure (input', posAccum, count')
Just st' -> go input'' st' (updatePosChar posAccum char') (count' + 1)

View file

@ -13,7 +13,9 @@ import Text.Parsec.Pos (updatePosChar)
Return everything consumed except for the end pattern itself. Return everything consumed except for the end pattern itself.
-} -}
takeUntil :: Text -> Parser Text takeUntil :: Text -> Parser Text
takeUntil end_ = Text.dropEnd (Text.length end_) <$> requireEnd (scan p (False, end)) >>= gotSome takeUntil end_ =
requireEnd (scan p (False, end))
>>= gotSome . Text.dropEnd (Text.length end_)
where where
end = Text.unpack end_ end = Text.unpack end_

View file

@ -9,6 +9,8 @@ module Types (
) )
where where
import Data.Foldable (fold)
newtype Document = Document newtype Document = Document
{ meta :: Meta { meta :: Meta
} }
@ -28,6 +30,7 @@ data Since = Since
-- Could have a better type? -- Could have a better type?
type Version = [Int] type Version = [Int]
type Package = String type Package = String
data DocMarkup mod id data DocMarkup mod id
@ -51,78 +54,78 @@ data DocMarkup mod id
| -- | Bold __bold text__ | -- | Bold __bold text__
DocBold (DocMarkup mod id) DocBold (DocMarkup mod id)
| {- | Unordered lists | {- | Unordered lists
* this * this
or or
- this - this
-} -}
DocUnorderedList [DocMarkup mod id] DocUnorderedList [DocMarkup mod id]
| {- | Ordered lists | {- | Ordered lists
1. this 1. this
or or
(1) this (1) this
-} -}
DocOrderedList [(Int, DocMarkup mod id)] DocOrderedList [(Int, DocMarkup mod id)]
| {- | Definition lists | {- | Definition lists
[term] a term [term] a term
[another term] another definition [another term] another definition
-} -}
DocDefinitionList [(DocMarkup mod id, DocMarkup mod id)] DocDefinitionList [(DocMarkup mod id, DocMarkup mod id)]
| {- | Code blocks | {- | Code blocks
@ @
a code block in here a code block in here
with multiple lines with multiple lines
@ @
Or with bird tracks: Or with bird tracks:
> some code > some code
> goes here > goes here
-} -}
DocCodeBlock (DocMarkup mod id) DocCodeBlock (DocMarkup mod id)
| {- | Hyperlinks | {- | Hyperlinks
__marked__: __marked__:
<http://example.com> <http://example.com>
<http://example.com label text> <http://example.com label text>
__Auto-detected URLs__: __Auto-detected URLs__:
http://example.com http://example.com
https://example.com https://example.com
ftp://example.com ftp://example.com
__Markdown style__ __Markdown style__
[link text](http://example.com) [link text](http://example.com)
[link text]("Module.Name") [link text]("Module.Name")
-} -}
DocHyperlink (Hyperlink (DocMarkup mod id)) DocHyperlink (Hyperlink (DocMarkup mod id))
| {- | Pictures | {- | Pictures
<<image.png>> <<image.png>>
<<image.png title text>> <<image.png title text>>
__Markdown Images__ __Markdown Images__
![alt text](image.png) ![alt text](image.png)
-} -}
DocPicture Picture DocPicture Picture
| {- | Inline math expressions | {- | Inline math expressions
\(mathematical expression\) \(mathematical expression\)
-} -}
DocMathInline String DocMathInline String
| {- | Math multiline display | {- | Math multiline display
\[ \[
mathematical expression mathematical expression
in multiple lines in multiple lines
\] \]
-} -}
DocMathDisplay String DocMathDisplay String
| {- | Anchors, no spaces allowed | {- | Anchors, no spaces allowed
#anchor-name# #anchor-name#
-} -}
DocAnchor String DocAnchor String
| {- | Property descriptions | {- | Property descriptions
prop> property description prop> property description
-} -}
DocProperty String DocProperty String
| {- | Examples | {- | Examples
>>> expression >>> expression
result line 1 result line 1
result line 2 result line 2
-} -}
DocExamples [Example] DocExamples [Example]
| -- | Header | -- | Header
@ -136,7 +139,7 @@ instance Semigroup (DocMarkup mod id) where
instance Monoid (DocMarkup mod id) where instance Monoid (DocMarkup mod id) where
mempty = DocEmpty mempty = DocEmpty
mconcat = foldr (<>) mempty mconcat = fold
data ModuleLink id = ModuleLink data ModuleLink id = ModuleLink
{ name :: String { name :: String

View file

@ -1,42 +1,40 @@
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -Wno-orphans #-} {-# OPTIONS_GHC -Wno-orphans #-}
import Test.Hspec import Data.String (IsString (..))
import Data.Text (Text)
import GHC.Stack
import Identifier (Identifier) import Identifier (Identifier)
import Lexer import Lexer
import Parser import Parser
import Types import Test.Hspec
import Data.String (IsString (..))
import Data.Text (Text)
import Text.Parsec.Pos import Text.Parsec.Pos
import GHC.Stack import Types
main :: IO () main :: IO ()
main = hspec $ do main = hspec $ do
describe "Lexer" do describe "Lexer" do
describe "minimal" do describe "minimal" do
it "handles unicode" unicode it "handles unicode" unicode
it "escapes" escaping it "escapes" escaping
it "maths" math it "maths" math
it "anchors" anchor 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
it "monospace" monospace it "monospace" monospace
it "labeled link" labeledLink it "labeled link" labeledLink
it "markdown link" link it "markdown link" link
it "bird tracks" birdTracks it "bird tracks" birdTracks
it "module names" modules it "module names" modules
it "quotes" quotes it "quotes" quotes
it "ignores nesting" ignoreNesting it "ignores nesting" ignoreNesting
describe "Parser" do describe "Parser" do
it "Bold" do it "Bold" do
"__bold__" `shouldParseTo` (DocBold (DocString "bold")) "__bold__" `shouldParseTo` DocBold (DocString "bold")
it "Emphasis" do it "Emphasis" do
"/emphasis/" `shouldParseTo` (DocEmphasis (DocString "emphasis")) "/emphasis/" `shouldParseTo` DocEmphasis (DocString "emphasis")
------------ ------------
-- Tests -- Tests
@ -44,137 +42,138 @@ main = hspec $ do
modules :: Expectation modules :: Expectation
modules = do modules = do
"\"MyModule.Name\"" "\"MyModule.Name\""
`shouldLexTo` [ (1, 2, Module "MyModule.Name") `shouldLexTo` [ (1, 2, Module "MyModule.Name")
] ]
"\"OtherModule.Name#myAnchor\"" "\"OtherModule.Name#myAnchor\""
`shouldLexTo` [ (1, 2, Module "OtherModule.Name") `shouldLexTo` [ (1, 2, Module "OtherModule.Name")
, (1, 18, Anchor "myAnchor") , (1, 18, Anchor "myAnchor")
] ]
"\"OtherModule.Name\\#myAnchor\""
`shouldLexTo` [ (1, 2, Module "OtherModule.Name")
, (1, 18, Anchor "myAnchor")
]
"\"OtherModule.Name\\#myAnchor\""
`shouldLexTo` [ (1, 2, Module "OtherModule.Name")
, (1, 18, Anchor "myAnchor")
]
link :: Expectation link :: Expectation
link = link =
"[link to](http://some.website)" "[link to](http://some.website)"
`shouldLexTo` [ (1, 1, LinkOpen) `shouldLexTo` [ (1, 1, LinkOpen)
, (1, 1, BracketOpen) , (1, 1, BracketOpen)
, (1, 2, Token "link to") , (1, 2, Token "link to")
, (1, 9, BracketClose) , (1, 9, BracketClose)
, (1, 10, ParenOpen) , (1, 10, ParenOpen)
, (1, 11, Token "http://some.website") , (1, 11, Token "http://some.website")
, (1, 30, ParenClose) , (1, 30, ParenClose)
, (1, 30, LinkClose) , (1, 30, LinkClose)
] ]
labeledLink :: Expectation labeledLink :: Expectation
labeledLink = labeledLink =
"<[link here](http://to.here) label>" "<[link here](http://to.here) label>"
`shouldLexTo` [ (1, 1, LabeledLinkOpen) `shouldLexTo` [ (1, 1, LabeledLinkOpen)
, (1, 2, BracketOpen) , (1, 2, BracketOpen)
, (1, 3, Token "link here") , (1, 3, Token "link here")
, (1, 12, BracketClose) , (1, 12, BracketClose)
, (1, 13, ParenOpen) , (1, 13, ParenOpen)
, (1, 14, Token "http://to.here") , (1, 14, Token "http://to.here")
, (1, 28, ParenClose) , (1, 28, ParenClose)
, (1, 29, Token " label") , (1, 29, Token " label")
, (1, 35, LabeledLinkClose) , (1, 35, LabeledLinkClose)
] ]
anchor :: Expectation anchor :: Expectation
anchor = anchor =
"#myAnchor#" "#myAnchor#"
`shouldLexTo` [ (1, 1, Anchor "myAnchor") `shouldLexTo` [ (1, 1, Anchor "myAnchor")
] ]
math :: IO () math :: IO ()
math = 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")
, (1, 12, MathMultilineClose) , (1, 12, MathMultilineClose)
] ]
"\\(other maths\\)" "\\(other maths\\)"
`shouldLexTo` [ (1, 1, MathInlineOpen) `shouldLexTo` [ (1, 1, MathInlineOpen)
, (1, 3, Token "other maths") , (1, 3, Token "other maths")
, (1, 14, MathInlineClose) , (1, 14, MathInlineClose)
] ]
escaping :: Expectation escaping :: Expectation
escaping = do escaping = do
"\\(" "\\("
`shouldLexTo` [ (1, 1, Escape) `shouldLexTo` [ (1, 1, Escape)
, (1, 2, Token "(") , (1, 2, Token "(")
] ]
"\\(\r\n" "\\(\r\n"
`shouldLexTo` [ (1, 1, Escape) `shouldLexTo` [ (1, 1, Escape)
, (1, 2, Token "(") , (1, 2, Token "(")
] ]
unicode :: Expectation unicode :: Expectation
unicode = unicode =
"ドラゴンクエストの冒険者🐉" "ドラゴンクエストの冒険者🐉"
`shouldLexTo` [ (1, 1, Token "ドラゴンクエストの冒険者🐉") `shouldLexTo` [ (1, 1, Token "ドラゴンクエストの冒険者🐉")
] ]
ignoreNesting :: Expectation ignoreNesting :: Expectation
ignoreNesting = ignoreNesting =
">/foo/" ">/foo/"
`shouldLexTo` [ (1, 1, Token ">/foo/") `shouldLexTo` [ (1, 1, Token ">/foo/")
] ]
birdTracks :: Expectation birdTracks :: Expectation
birdTracks = birdTracks =
">> code" ">> code"
`shouldLexTo` [ (1, 1, BirdTrack) `shouldLexTo` [ (1, 1, BirdTrack)
, (1, 4, Token "code") , (1, 4, Token "code")
] ]
quotes :: Expectation quotes :: Expectation
quotes = quotes =
"\"quoted\"" "\"quoted\""
`shouldLexTo` [ (1, 1, QuoteOpen) `shouldLexTo` [ (1, 1, QuoteOpen)
, (1, 2, Token "quoted") , (1, 2, Token "quoted")
, (1, 8, QuoteClose) , (1, 8, QuoteClose)
] ]
space :: Expectation space :: Expectation
space = do space = do
"\n " "\n "
`shouldLexTo` [ (1, 1, Newline) `shouldLexTo` [ (1, 1, Newline)
, (2, 1, Space) , (2, 1, Space)
] ]
" \n" " \n"
`shouldLexTo` [ (1, 1, Space) `shouldLexTo` [ (1, 1, Space)
, (1, 2, Newline) , (1, 2, Newline)
] ]
monospace :: Expectation monospace :: Expectation
monospace = monospace =
"@mono@" "@mono@"
`shouldLexTo` [ (1, 1, MonospaceOpen) `shouldLexTo` [ (1, 1, MonospaceOpen)
, (1, 2, Token "mono") , (1, 2, Token "mono")
, (1, 6, MonospaceClose) , (1, 6, MonospaceClose)
] ]
emphatic :: Expectation emphatic :: Expectation
emphatic = emphatic =
"/emphatic/" "/emphatic/"
`shouldLexTo` [ (1, 1, EmphasisOpen) `shouldLexTo` [ (1, 1, EmphasisOpen)
, (1, 2, Token "emphatic") , (1, 2, Token "emphatic")
, (1, 10, EmphasisClose) , (1, 10, EmphasisClose)
] ]
someString :: Expectation someString :: Expectation
someString = someString =
"some string" "some string"
`shouldLexTo` [ (1, 1, Token "some") `shouldLexTo` [ (1, 1, Token "some")
, (1, 5, Space) , (1, 5, Space)
, (1, 6, Token "string") , (1, 6, Token "string")
] ]
-------------- --------------
-- Helpers -- Helpers
@ -183,16 +182,16 @@ someString =
type Doc id = DocMarkup () id type Doc id = DocMarkup () id
instance IsString (Doc String) where instance IsString (Doc String) where
fromString = DocString fromString = DocString
shouldLexTo :: String -> [(Int, Int, Token)] -> Expectation shouldLexTo :: String -> [(Int, Int, Token)] -> Expectation
shouldLexTo input expected = shouldLexTo input expected =
withFrozenCallStack $ withFrozenCallStack $
case lexer input of case lexer input of
Right tokens -> do Right tokens -> do
let actual = map (\(pos, tok) -> (sourceLine pos, sourceColumn pos, tok)) tokens let actual = map (\(pos, tok) -> (sourceLine pos, sourceColumn pos, tok)) tokens
actual `shouldBe` expected actual `shouldBe` expected
Left err -> expectationFailure $ "Parse error: " <> show err Left err -> expectationFailure $ "Parse error: " <> show err
shouldParseTo :: Text -> DocMarkup mod Identifier -> Expectation shouldParseTo :: Text -> DocMarkup mod Identifier -> Expectation
shouldParseTo input ast = parseText input `shouldBe` ast shouldParseTo input ast = parseText input `shouldBe` ast