aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--data/templates/default.typst3
-rw-r--r--pandoc.cabal1
-rw-r--r--src/Text/Pandoc/Writers/Typst.hs76
-rw-r--r--test/Tests/Old.hs2
-rw-r--r--test/tables.typst130
-rw-r--r--test/tables/nordics.typst23
-rw-r--r--test/tables/planets.typst33
-rw-r--r--test/tables/students.typst26
-rw-r--r--test/writer.typst3
9 files changed, 193 insertions, 104 deletions
diff --git a/data/templates/default.typst b/data/templates/default.typst
index 25f105db2..ee4b8212f 100644
--- a/data/templates/default.typst
+++ b/data/templates/default.typst
@@ -10,7 +10,8 @@ $definitions.typst()$
}
#set table(
- inset: 6pt
+ inset: 6pt,
+ stroke: none
)
$if(template)$
diff --git a/pandoc.cabal b/pandoc.cabal
index a08cd20ca..27bb87e9f 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -326,6 +326,7 @@ extra-source-files:
test/tables/*.html4
test/tables/*.html5
test/tables/*.latex
+ test/tables/*.typst
test/tables/*.native
test/tables/*.mediawiki
test/tables/*.jats_archiving
diff --git a/src/Text/Pandoc/Writers/Typst.hs b/src/Text/Pandoc/Writers/Typst.hs
index 7c804ccd8..245d0ec87 100644
--- a/src/Text/Pandoc/Writers/Typst.hs
+++ b/src/Text/Pandoc/Writers/Typst.hs
@@ -20,12 +20,12 @@ import Text.Pandoc.Definition
import Text.Pandoc.Class ( PandocMonad)
import Text.Pandoc.Options ( WriterOptions(..), WrapOption(..), isEnabled )
import Data.Text (Text)
-import Data.List (intercalate)
+import Data.List (intercalate, intersperse)
import Network.URI (unEscapeString)
import qualified Data.Text as T
import Control.Monad.State ( StateT, evalStateT, gets, modify )
import Text.Pandoc.Writers.Shared ( metaToContext, defField, resetField,
- toLegacyTable, lookupMetaString,
+ lookupMetaString,
isOrderedListMarker )
import Text.Pandoc.Shared (isTightList, orderedListMarkers, tshow)
import Text.Pandoc.Writers.Math (convertMath)
@@ -34,6 +34,7 @@ import Text.DocLayout
import Text.DocTemplates (renderTemplate)
import Text.Pandoc.Extensions (Extension(..))
import Text.Collate.Lang (Lang(..), parseLang)
+import Text.Printf (printf)
import Data.Char (isAlphaNum)
-- | Convert Pandoc to Typst.
@@ -162,33 +163,80 @@ blockToTypst block =
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
+ Table (ident,_,_) (Caption _ caption) colspecs thead tbodies tfoot -> do
+ let lab = toLabel FreestandingLabel ident
capt' <- if null caption
then return mempty
else do
- captcontents <- inlinesToTypst caption
+ captcontents <- blocksToTypst caption
return $ ", caption: " <> brackets captcontents
- let lab = toLabel FreestandingLabel ident
+ let numcols = length colspecs
+ let (aligns, widths) = unzip colspecs
+ let commaSep = hcat . intersperse ", "
+ let toPercentage (ColWidth w) =
+ literal $ (T.dropWhileEnd (== '.') . T.dropWhileEnd (== '0'))
+ (T.pack (printf "%0.2f" (w * 100))) <> "%"
+ toPercentage ColWidthDefault = literal "auto"
+ let columns = if all (== ColWidthDefault) widths
+ then literal $ tshow numcols
+ else parens (commaSep (map toPercentage widths))
let formatalign AlignLeft = "left,"
formatalign AlignRight = "right,"
formatalign AlignCenter = "center,"
formatalign AlignDefault = "auto,"
let alignarray = parens $ mconcat $ map formatalign aligns
+ let fromCell (Cell _attr alignment rowspan colspan bs) = do
+ let cellattrs =
+ (case alignment of
+ AlignDefault -> []
+ AlignLeft -> [ "align: left" ]
+ AlignRight -> [ "align: right" ]
+ AlignCenter -> [ "align: center" ]) ++
+ (case rowspan of
+ RowSpan 1 -> []
+ RowSpan n -> [ "rowspan: " <> tshow n ]) ++
+ (case colspan of
+ ColSpan 1 -> []
+ ColSpan n -> [ "colspan: " <> tshow n ])
+ cellContents <- blocksToTypst bs
+ pure $ if null cellattrs
+ then brackets cellContents
+ else "table.cell" <>
+ parens
+ (literal (T.intercalate ", " cellattrs)) <>
+ brackets cellContents
+ let fromRow (Row _ cs) =
+ (<> ",") . commaSep <$> mapM fromCell cs
+ let fromHead (TableHead _attr headRows) =
+ if null headRows
+ then pure mempty
+ else (($$ "table.hline(),") .
+ (<> ",") . ("table.header" <>) . parens . nest 2 . vcat)
+ <$> mapM fromRow headRows
+ let fromFoot (TableFoot _attr footRows) =
+ if null footRows
+ then pure mempty
+ else (("table.hline()," $$) .
+ (<> ",") . ("table.footer" <>) . parens . nest 2 . vcat)
+ <$> mapM fromRow footRows
+ let fromTableBody (TableBody _attr _rowHeadCols headRows bodyRows) = do
+ hrows <- mapM fromRow headRows
+ brows <- mapM fromRow bodyRows
+ pure $ vcat (hrows ++ ["table.hline()," | not (null hrows)] ++ brows)
+ header <- fromHead thead
+ footer <- fromFoot tfoot
+ body <- vcat <$> mapM fromTableBody tbodies
return $
"#figure("
$$
nest 2
("align(center)[#table("
$$ nest 2
- ( "columns: " <> text (show numcols) <> "," -- auto
- $$ "align: (col, row) => " <> alignarray <> ".at(col),"
- $$ hsep (map ((<>",") . brackets) headers')
- $$ vcat (map (\x -> brackets x <> ",") (concat rows'))
+ ( "columns: " <> columns <> ","
+ $$ "align: " <> alignarray <> ","
+ $$ header
+ $$ body
+ $$ footer
)
$$ ")]"
$$ capt'
diff --git a/test/Tests/Old.hs b/test/Tests/Old.hs
index 7a07558ea..ca9988275 100644
--- a/test/Tests/Old.hs
+++ b/test/Tests/Old.hs
@@ -199,7 +199,7 @@ tests pandocPath =
[ testGroup "writer" $ writerTests' "ms"
]
, testGroup "typst"
- [ testGroup "writer" $ writerTests' "typst"
+ [ testGroup "writer" $ writerTests' "typst" ++ extWriterTests' "typst"
, testGroup "reader"
[ test' "typst-reader" ["-r", "typst", "-w", "native", "-s"]
"typst-reader.typ" "typst-reader.native"
diff --git a/test/tables.typst b/test/tables.typst
index 0eaa77600..3736a7193 100644
--- a/test/tables.typst
+++ b/test/tables.typst
@@ -3,20 +3,12 @@ Simple table with caption:
#figure(
align(center)[#table(
columns: 4,
- align: (col, row) => (right,left,center,auto,).at(col),
- [Right], [Left], [Center], [Default],
- [12],
- [12],
- [12],
- [12],
- [123],
- [123],
- [123],
- [123],
- [1],
- [1],
- [1],
- [1],
+ align: (right,left,center,auto,),
+ table.header([Right], [Left], [Center], [Default],),
+ table.hline(),
+ [12], [12], [12], [12],
+ [123], [123], [123], [123],
+ [1], [1], [1], [1],
)]
, caption: [Demonstration of simple table syntax.]
, kind: table
@@ -27,20 +19,12 @@ Simple table without caption:
#figure(
align(center)[#table(
columns: 4,
- align: (col, row) => (right,left,center,auto,).at(col),
- [Right], [Left], [Center], [Default],
- [12],
- [12],
- [12],
- [12],
- [123],
- [123],
- [123],
- [123],
- [1],
- [1],
- [1],
- [1],
+ align: (right,left,center,auto,),
+ table.header([Right], [Left], [Center], [Default],),
+ table.hline(),
+ [12], [12], [12], [12],
+ [123], [123], [123], [123],
+ [1], [1], [1], [1],
)]
, kind: table
)
@@ -50,20 +34,12 @@ Simple table indented two spaces:
#figure(
align(center)[#table(
columns: 4,
- align: (col, row) => (right,left,center,auto,).at(col),
- [Right], [Left], [Center], [Default],
- [12],
- [12],
- [12],
- [12],
- [123],
- [123],
- [123],
- [123],
- [1],
- [1],
- [1],
- [1],
+ align: (right,left,center,auto,),
+ table.header([Right], [Left], [Center], [Default],),
+ table.hline(),
+ [12], [12], [12], [12],
+ [123], [123], [123], [123],
+ [1], [1], [1], [1],
)]
, caption: [Demonstration of simple table syntax.]
, kind: table
@@ -73,17 +49,14 @@ Multiline table with caption:
#figure(
align(center)[#table(
- columns: 4,
- align: (col, row) => (center,left,right,left,).at(col),
- [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.],
+ columns: (15%, 13.75%, 16.25%, 35%),
+ align: (center,left,right,left,),
+ table.header([Centered Header], [Left Aligned], [Right Aligned], [Default
+ aligned],),
+ table.hline(),
+ [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.],
)]
, caption: [Here’s the caption. It may span multiple lines.]
, kind: table
@@ -93,17 +66,14 @@ Multiline table without caption:
#figure(
align(center)[#table(
- columns: 4,
- align: (col, row) => (center,left,right,left,).at(col),
- [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.],
+ columns: (15%, 13.75%, 16.25%, 35%),
+ align: (center,left,right,left,),
+ table.header([Centered Header], [Left Aligned], [Right Aligned], [Default
+ aligned],),
+ table.hline(),
+ [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.],
)]
, kind: table
)
@@ -113,19 +83,10 @@ Table without column headers:
#figure(
align(center)[#table(
columns: 4,
- align: (col, row) => (right,left,center,right,).at(col),
- [12],
- [12],
- [12],
- [12],
- [123],
- [123],
- [123],
- [123],
- [1],
- [1],
- [1],
- [1],
+ align: (right,left,center,right,),
+ [12], [12], [12], [12],
+ [123], [123], [123], [123],
+ [1], [1], [1], [1],
)]
, kind: table
)
@@ -134,16 +95,11 @@ Multiline table without column headers:
#figure(
align(center)[#table(
- columns: 4,
- align: (col, row) => (center,left,right,auto,).at(col),
- [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.],
+ columns: (15%, 13.75%, 16.25%, 35%),
+ align: (center,left,right,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.],
)]
, kind: table
)
diff --git a/test/tables/nordics.typst b/test/tables/nordics.typst
new file mode 100644
index 000000000..322d19845
--- /dev/null
+++ b/test/tables/nordics.typst
@@ -0,0 +1,23 @@
+#figure(
+ align(center)[#table(
+ columns: (30%, 30%, 20%, 20%),
+ align: (center,left,left,left,),
+ table.header(table.cell(align: center)[Name], table.cell(align: center)[Capital], table.cell(align: center)[Population
+ \
+ (in 2018)], table.cell(align: center)[Area \
+ (in km#super[2];)],),
+ table.hline(),
+ [Denmark], [Copenhagen], [5,809,502], [43,094],
+ [Finland], [Helsinki], [5,537,364], [338,145],
+ [Iceland], [Reykjavik], [343,518], [103,000],
+ [Norway], [Oslo], [5,372,191], [323,802],
+ [Sweden], [Stockholm], [10,313,447], [450,295],
+ table.hline(),
+ table.footer([Total], [], [27,376,022], [1,258,336],),
+ )]
+ , caption: [States belonging to the #emph[Nordics.]
+
+ ]
+ , kind: table
+ )
+<nordics>
diff --git a/test/tables/planets.typst b/test/tables/planets.typst
new file mode 100644
index 000000000..1d80ae88b
--- /dev/null
+++ b/test/tables/planets.typst
@@ -0,0 +1,33 @@
+#figure(
+ align(center)[#table(
+ columns: 12,
+ align: (center,center,auto,right,right,right,right,right,right,right,right,auto,),
+ table.header(table.cell(colspan: 2)[], [Name], [Mass (10^24kg)], [Diameter
+ (km)], [Density (kg/m^3)], [Gravity (m/s^2)], [Length of day
+ (hours)], [Distance from Sun (10^6km)], [Mean temperature (C)], [Number of
+ moons], [Notes],),
+ table.hline(),
+ table.cell(rowspan: 4, colspan: 2)[Terrestrial
+ planets], [Mercury], [0.330], [4,879], [5427], [3.7], [4222.6], [57.9], [167], [0], [Closest
+ to the Sun],
+ [Venus], [4.87], [12,104], [5243], [8.9], [2802.0], [108.2], [464], [0], [],
+ [Earth], [5.97], [12,756], [5514], [9.8], [24.0], [149.6], [15], [1], [Our
+ world],
+ [Mars], [0.642], [6,792], [3933], [3.7], [24.7], [227.9], [-65], [2], [The
+ red planet],
+ table.cell(rowspan: 4)[Jovian planets], table.cell(rowspan: 2)[Gas
+ giants], [Jupiter], [1898], [142,984], [1326], [23.1], [9.9], [778.6], [-110], [67], [The
+ largest planet],
+ [Saturn], [568], [120,536], [687], [9.0], [10.7], [1433.5], [-140], [62], [],
+ table.cell(rowspan: 2)[Ice
+ giants], [Uranus], [86.8], [51,118], [1271], [8.7], [17.2], [2872.5], [-195], [27], [],
+ [Neptune], [102], [49,528], [1638], [11.0], [16.1], [4495.1], [-200], [14], [],
+ table.cell(colspan: 2)[Dwarf
+ planets], [Pluto], [0.0146], [2,370], [2095], [0.7], [153.3], [5906.4], [-225], [5], [Declassified
+ as a planet in 2006.],
+ )]
+ , caption: [Data about the planets of our solar system.
+
+ ]
+ , kind: table
+ )
diff --git a/test/tables/students.typst b/test/tables/students.typst
new file mode 100644
index 000000000..223732b06
--- /dev/null
+++ b/test/tables/students.typst
@@ -0,0 +1,26 @@
+#figure(
+ align(center)[#table(
+ columns: (50%, 50%),
+ align: (left,left,),
+ table.header(table.cell(align: center)[Student
+ ID], table.cell(align: center)[Name],),
+ table.hline(),
+ table.cell(colspan: 2)[Computer Science],
+ table.hline(),
+ [3741255], [Jones, Martha],
+ [4077830], [Pierce, Benjamin],
+ [5151701], [Kirk, James],
+ table.cell(colspan: 2)[Russian Literature],
+ table.hline(),
+ [3971244], [Nim, Victor],
+ table.cell(colspan: 2)[Astrophysics],
+ table.hline(),
+ [4100332], [Petrov, Alexandra],
+ [4100332], [Toyota, Hiroko],
+ )]
+ , caption: [List of Students
+
+ ]
+ , kind: table
+ )
+<students>
diff --git a/test/writer.typst b/test/writer.typst
index e24de9a8a..9c5a8f921 100644
--- a/test/writer.typst
+++ b/test/writer.typst
@@ -16,7 +16,8 @@
}
#set table(
- inset: 6pt
+ inset: 6pt,
+ stroke: none
)
#let conf(