aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2023-03-21 21:08:02 -0700
committerJohn MacFarlane <[email protected]>2023-03-25 22:05:52 -0700
commit9edf965712d3795bd8cb3c5f2757204b0324aede (patch)
tree4daf2995b4d442b773b8346da29f55d269bed996
parentd8ec5c4b752c3fd09f0c5abdd7f1f5097835a6de (diff)
Add typst writer.
See #8713.
-rw-r--r--.github/workflows/ci.yml1
-rw-r--r--MANUAL.txt2
-rw-r--r--data/templates/default.typst93
-rw-r--r--pandoc.cabal5
-rw-r--r--src/Text/Pandoc/Extensions.hs2
-rw-r--r--src/Text/Pandoc/Format.hs1
-rw-r--r--src/Text/Pandoc/Writers.hs3
-rw-r--r--src/Text/Pandoc/Writers/Typst.hs293
-rw-r--r--test/Tests/Old.hs3
-rw-r--r--test/tables.typst142
-rw-r--r--test/writer.typst709
11 files changed, 1254 insertions, 0 deletions
diff --git a/.github/workflows/ci.yml b/.github/workflows/ci.yml
index 850ba89fc..348d2e83c 100644
--- a/.github/workflows/ci.yml
+++ b/.github/workflows/ci.yml
@@ -5,6 +5,7 @@ on:
branches:
- '*'
- '!rc/*'
+ - '!typst-writer'
paths-ignore:
- 'doc/*.md'
- 'MANUAL.txt'
diff --git a/MANUAL.txt b/MANUAL.txt
index cc97a5167..147c8e4e2 100644
--- a/MANUAL.txt
+++ b/MANUAL.txt
@@ -342,6 +342,7 @@ header when requesting a document from a URL:
- `revealjs` ([reveal.js] HTML5 + JavaScript slide show)
- `s5` ([S5] HTML and JavaScript slide show)
- `tei` ([TEI Simple])
+ - `typst` ([typst])
- `xwiki` ([XWiki markup])
- `zimwiki` ([ZimWiki markup])
- the path of a custom Lua writer, see [Custom readers and writers] below
@@ -515,6 +516,7 @@ header when requesting a document from a URL:
[BibLaTeX]: https://ctan.org/pkg/biblatex
[Markua]: https://leanpub.com/markua/read
[EndNote XML bibliography]: https://support.clarivate.com/Endnote/s/article/EndNote-XML-Document-Type-Definition
+[typst]: https://typst.app
## Reader options {.options}
diff --git a/data/templates/default.typst b/data/templates/default.typst
new file mode 100644
index 000000000..c6066dd24
--- /dev/null
+++ b/data/templates/default.typst
@@ -0,0 +1,93 @@
+#set page(
+$if(papersize)$
+ paper: "$papersize$",
+$endif$
+ numbering: "1"
+)
+#set par(justify: true)
+#set text(
+$if(lang)$
+ lang: "$lang$",
+$endif$
+$if(mainfont)$
+ font: "$mainfont$",
+$endif$
+$if(fontsize)$
+ size: $fontsize$,
+$endif$
+)
+#set heading(
+$if(numbering)$
+ numbering: "$numbering$"
+$endif$
+)
+
+#align(center)[#block(inset: 2em)[
+ #text(weight: "bold", size: 18pt)[$title$] \
+$for(author)$
+ $author$ \
+$endfor$
+$if(date)$
+ $date$
+$endif$
+]]
+
+#let definition(term, ..defs) = [
+ #strong(term) \
+ #(defs.pos().join("\n"))
+]
+
+#let blockquote(body) = [
+ #set text( size: 0.92em )
+ #block(inset: (left: 1.5em, top: 0.2em, bottom: 0.2em))[#body]
+]
+
+#let horizontalrule = [
+ #line(start: (25%,0%), end: (75%,0%))
+]
+
+#let endnote(num, contents) = [
+ #stack(dir: ltr, spacing: 3pt, super[#num], contents)
+]
+
+$if(columns)$
+#show: doc => columns($columns$, doc)
+$endif$
+
+$for(header-includes)$
+$header-includes$
+
+$endfor$
+$for(include-before)$
+$include-before$
+
+$endfor$
+$if(toc)$
+#outline(
+ title: auto,
+ depth: none
+);
+$endif$
+
+$body$
+
+#v(1em)
+#block[
+#horizontalrule
+#set text(size: .88em)
+#v(3pt) // otherwise first note marker is swallowed, bug?
+
+$notes$
+]
+$if(bibliographystyle)$
+
+#set bibliography(style: "$bibliographystyle$")
+$endif$
+$for(bibliography)$
+
+#bibliography("$bibliography$")
+$endfor$
+$for(include-after)$
+
+$include-after$
+$endfor$
diff --git a/pandoc.cabal b/pandoc.cabal
index cc540f542..538c5d3f9 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -25,6 +25,7 @@ description: Pandoc is a Haskell library for converting from one markup
- Documentation formats (GNU TexInfo, Haddock)
- Roff formats (man, ms)
- TeX formats (LaTeX, ConTeXt)
+ - Typst
- XML formats (DocBook 4 and 5, JATS, TEI Simple, OpenDocument)
- Outline formats (OPML)
- Bibliography formats (BibTeX, BibLaTeX, CSL JSON, CSL YAML,
@@ -94,6 +95,7 @@ data-files:
data/templates/article.jats_publishing
data/templates/affiliations.jats
data/templates/default.markua
+ data/templates/default.typst
-- translations
data/translations/*.yaml
-- entities
@@ -315,6 +317,7 @@ extra-source-files:
test/tables.asciidoctor
test/tables.haddock
test/tables.texinfo
+ test/tables.typst
test/tables.rst
test/tables.rtf
test/tables.txt
@@ -345,6 +348,7 @@ extra-source-files:
test/writer.plain
test/writer.mediawiki
test/writer.textile
+ test/writer.typst
test/writer.opendocument
test/writer.org
test/writer.asciidoc
@@ -589,6 +593,7 @@ library
Text.Pandoc.Writers.Jira,
Text.Pandoc.Writers.LaTeX,
Text.Pandoc.Writers.ConTeXt,
+ Text.Pandoc.Writers.Typst,
Text.Pandoc.Writers.OpenDocument,
Text.Pandoc.Writers.Texinfo,
Text.Pandoc.Writers.Man,
diff --git a/src/Text/Pandoc/Extensions.hs b/src/Text/Pandoc/Extensions.hs
index 97ac8e77a..efc5202a2 100644
--- a/src/Text/Pandoc/Extensions.hs
+++ b/src/Text/Pandoc/Extensions.hs
@@ -466,6 +466,7 @@ getDefaultExtensions "jats_articleauthoring" = getDefaultExtensions "jats"
getDefaultExtensions "opml" = pandocExtensions -- affects notes
getDefaultExtensions "markua" = extensionsFromList
[]
+getDefaultExtensions "typst" = extensionsFromList [Ext_citations]
getDefaultExtensions _ = extensionsFromList
[Ext_auto_identifiers]
@@ -644,4 +645,5 @@ getAllExtensions f = universalExtensions <> getAll f
getAll "mediawiki" = autoIdExtensions <>
extensionsFromList
[ Ext_smart ]
+ getAll "typst" = extensionsFromList [Ext_citations]
getAll _ = mempty
diff --git a/src/Text/Pandoc/Format.hs b/src/Text/Pandoc/Format.hs
index f79742d3f..ca04d4bc2 100644
--- a/src/Text/Pandoc/Format.hs
+++ b/src/Text/Pandoc/Format.hs
@@ -221,6 +221,7 @@ formatFromFilePath x =
".textile" -> defFlavor "textile"
".tsv" -> defFlavor "tsv"
".txt" -> defFlavor "markdown"
+ ".typ" -> defFlavor "typst"
".wiki" -> defFlavor "mediawiki"
".xhtml" -> defFlavor "html"
['.',y] | y `elem` ['1'..'9'] -> defFlavor "man"
diff --git a/src/Text/Pandoc/Writers.hs b/src/Text/Pandoc/Writers.hs
index 7f7a03603..c78b00dcf 100644
--- a/src/Text/Pandoc/Writers.hs
+++ b/src/Text/Pandoc/Writers.hs
@@ -72,6 +72,7 @@ module Text.Pandoc.Writers
, writeTEI
, writeTexinfo
, writeTextile
+ , writeTypst
, writeXWiki
, writeZimWiki
, getWriter
@@ -121,6 +122,7 @@ import Text.Pandoc.Writers.RTF
import Text.Pandoc.Writers.TEI
import Text.Pandoc.Writers.Texinfo
import Text.Pandoc.Writers.Textile
+import Text.Pandoc.Writers.Typst
import Text.Pandoc.Writers.XWiki
import Text.Pandoc.Writers.ZimWiki
@@ -177,6 +179,7 @@ writers = [
,("xwiki" , TextWriter writeXWiki)
,("zimwiki" , TextWriter writeZimWiki)
,("textile" , TextWriter writeTextile)
+ ,("typst" , TextWriter writeTypst)
,("rtf" , TextWriter writeRTF)
,("org" , TextWriter writeOrg)
,("asciidoc" , TextWriter writeAsciiDoc)
diff --git a/src/Text/Pandoc/Writers/Typst.hs b/src/Text/Pandoc/Writers/Typst.hs
new file mode 100644
index 000000000..bcecda035
--- /dev/null
+++ b/src/Text/Pandoc/Writers/Typst.hs
@@ -0,0 +1,293 @@
+{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE BangPatterns #-}
+{-# LANGUAGE LambdaCase #-}
+{-# LANGUAGE TupleSections #-}
+{-# LANGUAGE PatternGuards #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE TypeApplications #-}
+{-# LANGUAGE ViewPatterns #-}
+{- |
+ Module : Text.Pandoc.Writers.Typst
+ Copyright : Copyright (C) 2023 John MacFarlane
+ License : GNU GPL, version 2 or above
+
+ Maintainer : John MacFarlane <[email protected]>
+ Stability : alpha
+ Portability : portable
+
+Conversion of 'Pandoc' format into Typst markup
+(<https://typst.app>).
+-}
+module Text.Pandoc.Writers.Typst (
+ writeTypst
+ ) where
+import Text.Pandoc.Definition
+import Text.Pandoc.Class.PandocMonad ( PandocMonad )
+import Text.Pandoc.Options ( WriterOptions(..), WrapOption(..), isEnabled )
+import Data.Text (Text)
+import Data.List (intercalate, intersperse)
+import qualified Data.Text as T
+import Control.Monad.State ( StateT, evalStateT, gets, modify )
+import Text.Pandoc.Writers.Shared ( metaToContext, defField, toLegacyTable )
+import Text.Pandoc.Shared (isTightList, orderedListMarkers)
+import Text.Pandoc.Writers.Math (convertMath)
+import qualified Text.TeXMath as TM
+import Text.DocLayout
+import Text.DocTemplates (renderTemplate)
+import Text.Pandoc.Extensions (Extension(..))
+import Control.Monad (zipWithM)
+
+-- | Convert Pandoc to Typst.
+writeTypst :: PandocMonad m => WriterOptions -> Pandoc -> m Text
+writeTypst options document =
+ evalStateT (pandocToTypst options document)
+ WriterState{ stOptions = options, stNotes = [] }
+
+data WriterState =
+ WriterState {
+ stOptions :: WriterOptions,
+ stNotes :: [Doc Text]
+ }
+
+type TW m = StateT WriterState m
+
+pandocToTypst :: PandocMonad m
+ => WriterOptions -> Pandoc -> TW m Text
+pandocToTypst options (Pandoc meta blocks) = do
+ let colwidth = if writerWrapText options == WrapAuto
+ then Just $ writerColumns options
+ else Nothing
+ metadata <- metaToContext options
+ blocksToTypst
+ (fmap chomp . inlinesToTypst)
+ meta
+ main <- blocksToTypst blocks
+ noteContents <- reverse <$> gets stNotes
+ let notes = vsep $ zipWith
+ (\(num :: Int) cont ->
+ "#endnote" <> parens (brackets (text (show num))
+ <> ", " <> brackets (chomp cont)))
+ [1..] noteContents
+ let context = defField "body" main
+ $ defField "notes" notes
+ $ defField "toc" (writerTableOfContents options)
+ $ (if writerNumberSections options
+ then defField "numbering" ("1.1.1.1.1" :: Text)
+ else id)
+ $ metadata
+ return $ render colwidth $
+ case writerTemplate options of
+ Nothing -> main
+ Just tpl -> renderTemplate tpl context
+
+blocksToTypst :: PandocMonad m => [Block] -> TW m (Doc Text)
+blocksToTypst blocks = vcat <$> mapM blockToTypst blocks
+
+blockToTypst :: PandocMonad m => Block -> TW m (Doc Text)
+blockToTypst block =
+ case block of
+ Plain inlines -> inlinesToTypst inlines
+ Para inlines -> ($$ blankline) <$> inlinesToTypst inlines
+ Header level (ident,_,_) inlines -> do
+ contents <- inlinesToTypst inlines
+ let lab = toLabel ident
+ return $ literal (T.replicate level "=") <> space <> contents <> cr <> lab
+ RawBlock fmt str ->
+ case fmt of
+ Format "typst" -> return $ literal str
+ _ -> return mempty
+ CodeBlock (_,cls,_) code -> do
+ let go :: Char -> (Int, Int) -> (Int, Int)
+ go '`' (longest, current) =
+ let !new = current + 1 in (max longest new, new)
+ go _ (longest, _) = (longest, 0)
+ let (longestBacktickSequence, _) = T.foldr go (0,0) code
+ let fence = literal $ T.replicate (max 3 (longestBacktickSequence + 1)) "`"
+ let lang = case cls of
+ (cl:_) -> literal cl
+ _ -> mempty
+ return $ fence <> lang <> cr <> literal code <> cr <> fence <> blankline
+ LineBlock lns -> do
+ contents <- inlinesToTypst (intercalate [LineBreak] lns)
+ return $ contents <> blankline
+ BlockQuote blocks -> do
+ contents <- blocksToTypst blocks
+ return $ "#blockquote[" $$ chomp contents $$ "]" $$ blankline
+ HorizontalRule ->
+ return $ blankline <> "#horizontalrule" <> blankline
+ OrderedList attribs items -> do
+ items' <- zipWithM (\marker item ->
+ chomp <$> listItemToTypst 3 (literal marker) item)
+ (orderedListMarkers attribs) items
+ return $ (if isTightList items
+ then vcat items'
+ else vsep items') $$ blankline
+ BulletList items -> do
+ items' <- mapM (fmap chomp . listItemToTypst 2 "- ") items
+ return $ (if isTightList items
+ then vcat items'
+ else vsep items') $$ blankline
+ DefinitionList items ->
+ ($$ blankline) . vsep <$> mapM defListItemToTypst items
+ Table (ident,_,_) blkCapt colspecs thead tbodies tfoot -> do
+ let (caption, aligns, _, headers, rows) =
+ toLegacyTable blkCapt colspecs thead tbodies tfoot
+ let numcols = length aligns
+ headers' <- mapM blocksToTypst headers
+ rows' <- mapM (mapM blocksToTypst) rows
+ capt' <- if null caption
+ then return mempty
+ else do
+ captcontents <- inlinesToTypst caption
+ return $ "#align(center, " <> brackets captcontents <> ")"
+ let lab = toLabel ident
+ -- TODO figure out how to specify alignment
+ -- let formatalign AlignLeft = "left"
+ -- formatalign AlignRight = "right"
+ -- formatalign AlignCenter = "center"
+ -- formatalign AlignDefault = "left"
+ -- let alignspecs = map formatalign aligns
+ return $ "#align(center)[#table("
+ $$ nest 2
+ ( "columns: " <> text (show numcols) <> "," -- auto
+ $$ "inset: 6pt" <> ","
+ $$ "align: auto,"
+ $$ hsep (map ((<>",") . brackets) headers')
+ $$ vcat (map (\x -> brackets x <> ",") (concat rows'))
+ )
+ $$ ")"
+ $$ capt'
+ $$ lab
+ $$ "]"
+ $$ blankline
+ Figure (ident,_,_) (Caption _mbshort capt) blocks -> do
+ caption <- blocksToTypst capt
+ contents <- blocksToTypst blocks
+ let lab = toLabel ident
+ return $ "#figure(" <> nest 2 (brackets contents <> "," <> cr <>
+ ("caption: [" $$ nest 2 caption $$ "]"))
+ <> cr <> ")" <> lab <> blankline
+ Div (ident,_,_) blocks -> do
+ let lab = toLabel ident
+ contents <- blocksToTypst blocks
+ return $ lab <> contents
+
+defListItemToTypst :: PandocMonad m => ([Inline], [[Block]]) -> TW m (Doc Text)
+defListItemToTypst (term, defns) = do
+ term' <- inlinesToTypst term
+ defns' <- mapM blocksToTypst defns
+ return $ "#definition" <> brackets term' <> mconcat (map brackets defns')
+
+listItemToTypst :: PandocMonad m => Int -> Doc Text -> [Block] -> TW m (Doc Text)
+listItemToTypst ind marker blocks = do
+ contents <- blocksToTypst blocks
+ return $ hang ind (marker <> space) contents
+
+inlinesToTypst :: PandocMonad m => [Inline] -> TW m (Doc Text)
+inlinesToTypst ils = hcat <$> mapM inlineToTypst ils
+
+inlineToTypst :: PandocMonad m => Inline -> TW m (Doc Text)
+inlineToTypst inline =
+ case inline of
+ Str txt -> return $ literal $ escapeTypst txt
+ Space -> return space
+ SoftBreak -> do
+ wrapText <- gets $ writerWrapText . stOptions
+ case wrapText of
+ WrapPreserve -> return cr
+ WrapAuto -> return space
+ WrapNone -> return space
+ LineBreak -> return (space <> "\\" <> cr)
+ Math mathType str -> do
+ res <- convertMath TM.writeTypst mathType str
+ case res of
+ Left il -> inlineToTypst il
+ Right r ->
+ case mathType of
+ InlineMath -> return $ "$" <> literal r <> "$"
+ DisplayMath -> return $ "$ " <> literal r <> " $"
+ Code (_,cls,_) code -> return $
+ case cls of
+ (lang:_) -> "#raw(lang=" <> doubleQuotes (literal lang) <>
+ ", " <> doubleQuotes (literal code) <> ")"
+ _ | T.any (=='`') code -> "#raw(" <> doubleQuotes (literal code) <> ")"
+ | otherwise -> "`" <> literal code <> "`"
+ RawInline fmt str ->
+ case fmt of
+ Format "typst" -> return $ literal str
+ _ -> return mempty
+ Strikeout inlines -> textstyle "#strike" inlines
+ Emph inlines -> textstyle "#emph" inlines
+ Underline inlines -> textstyle "#underline" inlines
+ Strong inlines -> textstyle "#strong" inlines
+ Superscript inlines -> textstyle "#super" inlines
+ Subscript inlines -> textstyle "#sub" inlines
+ SmallCaps inlines -> textstyle "#smallcaps" inlines
+ Span (ident,_,_) inlines -> do
+ let lab = toLabel ident
+ (lab $$) <$> inlinesToTypst inlines
+ Quoted quoteType inlines -> do
+ let q = case quoteType of
+ DoubleQuote -> literal "\""
+ SingleQuote -> literal "'"
+ contents <- inlinesToTypst inlines
+ return $ q <> contents <> q
+ Cite citations inlines -> do
+ opts <- gets stOptions
+ if isEnabled Ext_citations opts
+ then return $ -- Note: this loses locators, prefix, suffix
+ "#cite" <> parens
+ (mconcat $ intersperse ", " $
+ map (doubleQuotes . literal . citationId) citations)
+ else inlinesToTypst inlines
+ Link _attrs inlines (src,_tit) -> do
+ contents <- inlinesToTypst inlines
+ return $ "#link" <> parens (doubleQuotes (literal src)) <>
+ if render Nothing contents == src
+ then mempty
+ else nowrap $ brackets contents
+ Image (_,_,kvs) _inlines (src,_tit) -> do
+ let width' = maybe mempty ((", width: " <>) . literal) $ lookup "width" kvs
+ let height' = maybe mempty ((", height: " <>) . literal) $
+ lookup "height" kvs
+ return $ "#image(" <> doubleQuotes (literal src) <> width' <> height' <> ")"
+ Note blocks -> do -- currently typst has no footnotes!
+ -- TODO create endnotes with manual typesetting
+ contents <- blocksToTypst blocks
+ modify $ \st -> st{ stNotes = contents : stNotes st }
+ num <- text . show . length <$> gets stNotes
+ return $ "#super" <> brackets num
+
+textstyle :: PandocMonad m => Doc Text -> [Inline] -> TW m (Doc Text)
+textstyle s inlines = (s <>) . brackets <$> inlinesToTypst inlines
+
+escapeTypst :: Text -> Text
+escapeTypst t =
+ if T.any needsEscape t
+ then T.concatMap escapeChar t
+ else t
+ where
+ escapeChar c
+ | needsEscape c = "\\" <> T.singleton c
+ | otherwise = T.singleton c
+ needsEscape '[' = True
+ needsEscape ']' = True
+ needsEscape '#' = True
+ needsEscape '<' = True
+ needsEscape '>' = True
+ needsEscape '@' = True
+ needsEscape '$' = True
+ needsEscape '\\' = True
+ needsEscape '\'' = True
+ needsEscape '"' = True
+ needsEscape '`' = True
+ needsEscape '=' = True
+ needsEscape '_' = True
+ needsEscape '*' = True
+ needsEscape _ = False
+
+toLabel :: Text -> Doc Text
+toLabel ident =
+ if T.null ident
+ then mempty
+ else "#label" <> parens (doubleQuotes (literal ident))
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index 957a41287..81a5adbf2 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -193,6 +193,9 @@ tests pandocPath =
, testGroup "ms"
[ testGroup "writer" $ writerTests' "ms"
]
+ , testGroup "typst"
+ [ testGroup "writer" $ writerTests' "typst"
+ ]
, testGroup "creole"
[ test' "reader" ["-r", "creole", "-w", "native", "-s"]
"creole-reader.txt" "creole-reader.native"
diff --git a/test/tables.typst b/test/tables.typst
new file mode 100644
index 000000000..0d516b0e0
--- /dev/null
+++ b/test/tables.typst
@@ -0,0 +1,142 @@
+Simple table with caption:
+
+#align(center)[#table(
+ columns: 4,
+ inset: 6pt,
+ align: auto,
+ [Right], [Left], [Center], [Default],
+ [12],
+ [12],
+ [12],
+ [12],
+ [123],
+ [123],
+ [123],
+ [123],
+ [1],
+ [1],
+ [1],
+ [1],
+)
+#align(center, [Demonstration of simple table syntax.])
+]
+
+Simple table without caption:
+
+#align(center)[#table(
+ columns: 4,
+ inset: 6pt,
+ align: auto,
+ [Right], [Left], [Center], [Default],
+ [12],
+ [12],
+ [12],
+ [12],
+ [123],
+ [123],
+ [123],
+ [123],
+ [1],
+ [1],
+ [1],
+ [1],
+)
+]
+
+Simple table indented two spaces:
+
+#align(center)[#table(
+ columns: 4,
+ inset: 6pt,
+ align: auto,
+ [Right], [Left], [Center], [Default],
+ [12],
+ [12],
+ [12],
+ [12],
+ [123],
+ [123],
+ [123],
+ [123],
+ [1],
+ [1],
+ [1],
+ [1],
+)
+#align(center, [Demonstration of simple table syntax.])
+]
+
+Multiline table with caption:
+
+#align(center)[#table(
+ columns: 4,
+ inset: 6pt,
+ align: auto,
+ [Centered Header], [Left Aligned], [Right Aligned], [Default aligned],
+ [First],
+ [row],
+ [12.0],
+ [Example of a row that spans multiple lines.],
+ [Second],
+ [row],
+ [5.0],
+ [Here’s another one. Note the blank line between rows.],
+)
+#align(center, [Here’s the caption. It may span multiple lines.])
+]
+
+Multiline table without caption:
+
+#align(center)[#table(
+ columns: 4,
+ inset: 6pt,
+ align: auto,
+ [Centered Header], [Left Aligned], [Right Aligned], [Default aligned],
+ [First],
+ [row],
+ [12.0],
+ [Example of a row that spans multiple lines.],
+ [Second],
+ [row],
+ [5.0],
+ [Here’s another one. Note the blank line between rows.],
+)
+]
+
+Table without column headers:
+
+#align(center)[#table(
+ columns: 4,
+ inset: 6pt,
+ align: auto,
+ [12],
+ [12],
+ [12],
+ [12],
+ [123],
+ [123],
+ [123],
+ [123],
+ [1],
+ [1],
+ [1],
+ [1],
+)
+]
+
+Multiline table without column headers:
+
+#align(center)[#table(
+ columns: 4,
+ inset: 6pt,
+ align: auto,
+ [First],
+ [row],
+ [12.0],
+ [Example of a row that spans multiple lines.],
+ [Second],
+ [row],
+ [5.0],
+ [Here’s another one. Note the blank line between rows.],
+)
+]
diff --git a/test/writer.typst b/test/writer.typst
new file mode 100644
index 000000000..aa14a59a6
--- /dev/null
+++ b/test/writer.typst
@@ -0,0 +1,709 @@
+#set page(
+ numbering: "1"
+)
+#set par(justify: true)
+#set text(
+)
+#set heading(
+)
+
+#align(center)[#block(inset: 2em)[
+ #text(weight: "bold", size: 18pt)[Pandoc Test Suite] \
+ John MacFarlane \
+ Anonymous \
+ July 17, 2006
+]]
+
+#let definition(term, ..defs) = [
+ #strong(term) \
+ #(defs.pos().join("\n"))
+]
+
+#let blockquote(body) = [
+ #set text( size: 0.92em )
+ #block(inset: (left: 1.5em, top: 0.2em, bottom: 0.2em))[#body]
+]
+
+#let horizontalrule = [
+ #line(start: (25%,0%), end: (75%,0%))
+]
+
+#let endnote(num, contents) = [
+ #stack(dir: ltr, spacing: 3pt, super[#num], contents)
+]
+
+
+
+This is a set of tests for pandoc. Most of them are adapted from John Gruber’s
+markdown test suite.
+
+#horizontalrule
+
+= Headers
+#label("headers")
+== Level 2 with an #link("/url")[embedded link]
+#label("level-2-with-an-embedded-link")
+=== Level 3 with #emph[emphasis]
+#label("level-3-with-emphasis")
+==== Level 4
+#label("level-4")
+===== Level 5
+#label("level-5")
+= Level 1
+#label("level-1")
+== Level 2 with #emph[emphasis]
+#label("level-2-with-emphasis")
+=== Level 3
+#label("level-3")
+with no blank line
+
+== Level 2
+#label("level-2")
+with no blank line
+
+#horizontalrule
+
+= Paragraphs
+#label("paragraphs")
+Here’s a regular paragraph.
+
+In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item.
+Because a hard-wrapped line in the middle of a paragraph looked like a list
+item.
+
+Here’s one with a bullet. \* criminey.
+
+There should be a hard line break \
+here.
+
+#horizontalrule
+
+= Block Quotes
+#label("block-quotes")
+E-mail style:
+
+#blockquote[
+This is a block quote. It is pretty short.
+]
+
+#blockquote[
+Code in a block quote:
+
+```
+sub status {
+ print "working";
+}
+```
+
+A list:
+
+1. item one
+2. item two
+
+Nested block quotes:
+
+#blockquote[
+nested
+]
+
+#blockquote[
+nested
+]
+]
+
+This should not be a block quote: 2 \> 1.
+
+And a following paragraph.
+
+#horizontalrule
+
+= Code Blocks
+#label("code-blocks")
+Code:
+
+```
+---- (should be four hyphens)
+
+sub status {
+ print "working";
+}
+
+this code block is indented by one tab
+```
+
+And:
+
+```
+ this code block is indented by two tabs
+
+These should not be escaped: \$ \\ \> \[ \{
+```
+
+#horizontalrule
+
+= Lists
+#label("lists")
+== Unordered
+#label("unordered")
+Asterisks tight:
+
+- asterisk 1
+- asterisk 2
+- asterisk 3
+
+Asterisks loose:
+
+- asterisk 1
+
+- asterisk 2
+
+- asterisk 3
+
+Pluses tight:
+
+- Plus 1
+- Plus 2
+- Plus 3
+
+Pluses loose:
+
+- Plus 1
+
+- Plus 2
+
+- Plus 3
+
+Minuses tight:
+
+- Minus 1
+- Minus 2
+- Minus 3
+
+Minuses loose:
+
+- Minus 1
+
+- Minus 2
+
+- Minus 3
+
+== Ordered
+#label("ordered")
+Tight:
+
+1. First
+2. Second
+3. Third
+
+and:
+
+1. One
+2. Two
+3. Three
+
+Loose using tabs:
+
+1. First
+
+2. Second
+
+3. Third
+
+and using spaces:
+
+1. One
+
+2. Two
+
+3. Three
+
+Multiple paragraphs:
+
+1. Item 1, graf one.
+
+ Item 1. graf two. The quick brown fox jumped over the lazy dog’s back.
+
+2. Item 2.
+
+3. Item 3.
+
+== Nested
+#label("nested")
+- Tab
+ - Tab
+ - Tab
+
+Here’s another:
+
+1. First
+2. Second:
+ - Fee
+ - Fie
+ - Foe
+3. Third
+
+Same thing but with paragraphs:
+
+1. First
+
+2. Second:
+
+ - Fee
+ - Fie
+ - Foe
+
+3. Third
+
+== Tabs and spaces
+#label("tabs-and-spaces")
+- this is a list item indented with tabs
+
+- this is a list item indented with spaces
+
+ - this is an example list item indented with tabs
+
+ - this is an example list item indented with spaces
+
+== Fancy list markers
+#label("fancy-list-markers")
+(2) begins with 2
+
+(3) and now 3
+
+ with a continuation
+
+ iv. sublist with roman numerals, starting with 4
+ v. more items
+ (A) a subsublist
+ (B) a subsublist
+
+Nesting:
+
+A. Upper Alpha
+ I. Upper Roman.
+ (6) Decimal start with 6
+ c) Lower alpha with paren
+
+Autonumbering:
+
+1. Autonumber.
+2. More.
+ 1. Nested.
+
+Should not be a list item:
+
+M.A. 2007
+
+B. Williams
+
+#horizontalrule
+
+= Definition Lists
+#label("definition-lists")
+Tight using spaces:
+
+#definition[apple][red fruit]
+
+#definition[orange][orange fruit]
+
+#definition[banana][yellow fruit]
+
+Tight using tabs:
+
+#definition[apple][red fruit]
+
+#definition[orange][orange fruit]
+
+#definition[banana][yellow fruit]
+
+Loose:
+
+#definition[apple][red fruit
+
+]
+
+#definition[orange][orange fruit
+
+]
+
+#definition[banana][yellow fruit
+
+]
+
+Multiple blocks with italics:
+
+#definition[#emph[apple]][red fruit
+
+contains seeds, crisp, pleasant to taste
+
+]
+
+#definition[#emph[orange]][orange fruit
+
+```
+{ orange code block }
+```
+
+#blockquote[
+orange block quote
+]
+
+]
+
+Multiple definitions, tight:
+
+#definition[apple][red fruit][computer]
+
+#definition[orange][orange fruit][bank]
+
+Multiple definitions, loose:
+
+#definition[apple][red fruit
+
+][computer
+
+]
+
+#definition[orange][orange fruit
+
+][bank
+
+]
+
+Blank line after term, indented marker, alternate markers:
+
+#definition[apple][red fruit
+
+][computer
+
+]
+
+#definition[orange][orange fruit
+
+1. sublist
+2. sublist
+
+]
+
+= HTML Blocks
+#label("html-blocks")
+Simple block on one line:
+
+foo
+And nested without indentation:
+
+foo
+
+bar
+Interpreted markdown in a table:
+
+This is #emph[emphasized]
+And this is #strong[strong]
+Here’s a simple block:
+
+foo
+
+This should be a code block, though:
+
+```
+<div>
+ foo
+</div>
+```
+
+As should this:
+
+```
+<div>foo</div>
+```
+
+Now, nested:
+
+foo
+This should just be an HTML comment:
+
+Multiline:
+
+Code block:
+
+```
+<!-- Comment -->
+```
+
+Just plain comment, with trailing spaces on the line:
+
+Code:
+
+```
+<hr />
+```
+
+Hr’s:
+
+#horizontalrule
+
+= Inline Markup
+#label("inline-markup")
+This is #emph[emphasized], and so #emph[is this].
+
+This is #strong[strong], and so #strong[is this].
+
+An #emph[#link("/url")[emphasized link]].
+
+#strong[#emph[This is strong and em.]]
+
+So is #strong[#emph[this]] word.
+
+#strong[#emph[This is strong and em.]]
+
+So is #strong[#emph[this]] word.
+
+This is code: `>`, `$`, `\`, `\$`, `<html>`.
+
+#strike[This is #emph[strikeout].]
+
+Superscripts: a#super[bc]d a#super[#emph[hello]] a#super[hello there].
+
+Subscripts: H#sub[2]O, H#sub[23]O, H#sub[many of them]O.
+
+These should not be superscripts or subscripts, because of the unescaped spaces:
+a^b c^d, a~b c~d.
+
+#horizontalrule
+
+= Smart quotes, ellipses, dashes
+#label("smart-quotes-ellipses-dashes")
+"Hello," said the spider. "'Shelob' is my name."
+
+'A', 'B', and 'C' are letters.
+
+'Oak,' 'elm,' and 'beech' are names of trees. So is 'pine.'
+
+'He said, "I want to go."' Were you alive in the 70’s?
+
+Here is some quoted '`code`' and a
+"#link("http://example.com/?foo=1&bar=2")[quoted link]".
+
+Some dashes: one—two — three—four — five.
+
+Dashes between numbers: 5–7, 255–66, 1987–1999.
+
+Ellipses…and…and….
+
+#horizontalrule
+
+= LaTeX
+#label("latex")
+-
+- $2 plus 2 eq 4$
+- $x in y$
+- $alpha and omega$
+- $223$
+- $p$-Tree
+- Here’s some display math:
+ $ frac(d, d x) f lr((x)) eq lim_(h arrow.r 0) frac(f lr((x plus h)) minus f lr((x)), h) $
+- Here’s one that has a line break in it: $alpha plus omega times x^2$.
+
+These shouldn’t be math:
+
+- To get the famous equation, write `$e = mc^2$`.
+- \$22,000 is a #emph[lot] of money. So is \$34,000. (It worked if "lot" is
+ emphasized.)
+- Shoes (\$20) and socks (\$5).
+- Escaped `$`: \$73 #emph[this should be emphasized] 23\$.
+
+Here’s a LaTeX table:
+
+#horizontalrule
+
+= Special Characters
+#label("special-characters")
+Here is some unicode:
+
+- I hat: Î
+- o umlaut: ö
+- section: §
+- set membership: ∈
+- copyright: ©
+
+AT&T has an ampersand in their name.
+
+AT&T is another way to write it.
+
+This & that.
+
+4 \< 5.
+
+6 \> 5.
+
+Backslash: \\
+
+Backtick: \`
+
+Asterisk: \*
+
+Underscore: \_
+
+Left brace: {
+
+Right brace: }
+
+Left bracket: \[
+
+Right bracket: \]
+
+Left paren: (
+
+Right paren: )
+
+Greater-than: \>
+
+Hash: \#
+
+Period: .
+
+Bang: !
+
+Plus: +
+
+Minus: -
+
+#horizontalrule
+
+= Links
+#label("links")
+== Explicit
+#label("explicit")
+Just a #link("/url/")[URL].
+
+#link("/url/")[URL and title].
+
+#link("/url/")[URL and title].
+
+#link("/url/")[URL and title].
+
+#link("/url/")[URL and title]
+
+#link("/url/")[URL and title]
+
+#link("/url/with_underscore")[with\_underscore]
+
+#link("mailto:[email protected]")[Email link]
+
+#link("")[Empty].
+
+== Reference
+#label("reference")
+Foo #link("/url/")[bar].
+
+With #link("/url/")[embedded \[brackets\]].
+
+#link("/url/")[b] by itself should be a link.
+
+Indented #link("/url")[once].
+
+Indented #link("/url")[twice].
+
+Indented #link("/url")[thrice].
+
+This should \[not\]\[\] be a link.
+
+```
+[not]: /url
+```
+
+Foo #link("/url/")[bar].
+
+Foo #link("/url/")[biz].
+
+== With ampersands
+#label("with-ampersands")
+Here’s a
+#link("http://example.com/?foo=1&bar=2")[link with an ampersand in the URL].
+
+Here’s a link with an amersand in the link text: #link("http://att.com/")[AT&T].
+
+Here’s an #link("/script?foo=1&bar=2")[inline link].
+
+Here’s an #link("/script?foo=1&bar=2")[inline link in pointy braces].
+
+== Autolinks
+#label("autolinks")
+With an ampersand:
+#link("http://example.com/?foo=1&bar=2")[http://example.com/?foo\=1&bar\=2]
+
+- In a list?
+- #link("http://example.com/")
+- It should.
+
+An e-mail address: #link("mailto:[email protected]")[nobody\@nowhere.net]
+
+#blockquote[
+Blockquoted: #link("http://example.com/")
+]
+
+Auto-links should not occur here: `<http://example.com/>`
+
+```
+or here: <http://example.com/>
+```
+
+#horizontalrule
+
+= Images
+#label("images")
+From "Voyage dans la Lune" by Georges Melies (1902):
+
+#figure([#image("lalune.jpg")],
+ caption: [
+ lalune
+ ]
+)
+
+Here is a movie #image("movie.jpg") icon.
+
+#horizontalrule
+
+= Footnotes
+#label("footnotes")
+Here is a footnote reference,#super[1] and another.#super[2] This should
+#emph[not] be a footnote reference, because it contains a space.\[^my note\]
+Here is an inline note.#super[3]
+
+#blockquote[
+Notes can go in quotes.#super[4]
+]
+
+1. And in list items.#super[5]
+
+This paragraph should not be part of the note, as it is not indented.
+
+#v(1em)
+#block[
+#horizontalrule
+#set text(size: .88em)
+#v(3pt) // otherwise first note marker is swallowed, bug?
+
+#endnote([1], [Here is the footnote. It can go anywhere after the footnote
+reference. It need not be placed at the end of the document.])
+
+#endnote([2], [Here’s the long note. This one contains multiple blocks.
+
+Subsequent blocks are indented to show that they belong to the footnote (as with
+list items).
+
+```
+ { <code> }
+```
+
+If you want, you can indent every line, but you can also be lazy and just indent
+the first line of each block.])
+
+#endnote([3], [This is #emph[easier] to type. Inline notes may contain
+#link("http://google.com")[links] and `]` verbatim characters, as well as
+\[bracketed text\].])
+
+#endnote([4], [In quote.])
+
+#endnote([5], [In list.])
+]