Use pretty-simple to format native output.

Previously we used our own homespun formatting.  But this
produces over-long lines that aren't ideal for diffs in tests.
Easier to use something off-the-shelf and standard.

Closes #7580.

Performance is slower by about a factor of 10, but this isn't
really a problem because native isn't suitable as a serialization
format. (For serialization you should use json, because the reader
is so much faster than native.)
This commit is contained in:
John MacFarlane 2021-09-19 12:09:51 -07:00
parent 5f7e7f539a
commit c266734448
269 changed files with 65524 additions and 11857 deletions

View file

@ -583,7 +583,8 @@ library
xml-conduit >= 1.9.1.1 && < 1.10,
unicode-collation >= 0.1.1 && < 0.2,
zip-archive >= 0.2.3.4 && < 0.5,
zlib >= 0.5 && < 0.7
zlib >= 0.5 && < 0.7,
pretty-simple >= 4.0 && < 4.1
if os(windows) && arch(i386)
build-depends: basement >= 0.0.10,
foundation >= 0.0.23

View file

@ -12,82 +12,24 @@ Conversion of a 'Pandoc' document to a string representation.
-}
module Text.Pandoc.Writers.Native ( writeNative )
where
import Data.List (intersperse)
import Data.Text (Text)
import qualified Data.Text.Lazy as TL
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition
import Text.Pandoc.Options (WrapOption (..), WriterOptions (..))
import Text.DocLayout
prettyList :: [Doc Text] -> Doc Text
prettyList ds =
"[" <>
mconcat (intersperse (cr <> ",") $ map (nest 1) ds) <> "]"
-- | Prettyprint Pandoc block element.
prettyBlock :: Block -> Doc Text
prettyBlock (LineBlock lines') =
"LineBlock" $$ prettyList (map (text . show) lines')
prettyBlock (BlockQuote blocks) =
"BlockQuote" $$ prettyList (map prettyBlock blocks)
prettyBlock (OrderedList attribs blockLists) =
"OrderedList" <> space <> text (show attribs) $$
prettyList (map (prettyList . map prettyBlock) blockLists)
prettyBlock (BulletList blockLists) =
"BulletList" $$
prettyList (map (prettyList . map prettyBlock) blockLists)
prettyBlock (DefinitionList items) = "DefinitionList" $$
prettyList (map deflistitem items)
where deflistitem (term, defs) = "(" <> text (show term) <> "," <> cr <>
nest 1 (prettyList $ map (prettyList . map prettyBlock) defs) <> ")"
prettyBlock (Table attr blkCapt specs thead tbody tfoot) =
mconcat [ "Table "
, text (show attr)
, " "
, prettyCaption blkCapt ] $$
prettyList (map (text . show) specs) $$
prettyHead thead $$
prettyBodies tbody $$
prettyFoot tfoot
where prettyRows = prettyList . map prettyRow
prettyRow (Row a body) =
text ("Row " <> show a) $$ prettyList (map prettyCell body)
prettyCell (Cell a ma h w b) =
mconcat [ "Cell "
, text (show a)
, " "
, text (show ma)
, " ("
, text (show h)
, ") ("
, text (show w)
, ")" ] $$
prettyList (map prettyBlock b)
prettyCaption (Caption mshort body) =
"(Caption " <> text (showsPrec 11 mshort "") $$ prettyList (map prettyBlock body) <> ")"
prettyHead (TableHead thattr body)
= "(TableHead " <> text (show thattr) $$ prettyRows body <> ")"
prettyBody (TableBody tbattr rhc hd bd)
= mconcat [ "(TableBody "
, text (show tbattr)
, " ("
, text (show rhc)
, ")" ] $$ prettyRows hd $$ prettyRows bd <> ")"
prettyBodies = prettyList . map prettyBody
prettyFoot (TableFoot tfattr body)
= "(TableFoot " <> text (show tfattr) $$ prettyRows body <> ")"
prettyBlock (Div attr blocks) =
text ("Div " <> show attr) $$ prettyList (map prettyBlock blocks)
prettyBlock block = text $ show block
import Text.Pandoc.Options (WriterOptions (..))
import Text.Pretty.Simple (pShowOpt, defaultOutputOptionsNoColor,
OutputOptions(..), StringOutputStyle(..))
-- | Prettyprint Pandoc document.
writeNative :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeNative opts (Pandoc meta blocks) = return $
let colwidth = if writerWrapText opts == WrapAuto
then Just $ writerColumns opts
else Nothing
withHead = case writerTemplate opts of
Just _ -> \bs -> text ("Pandoc (" ++ show meta ++ ")") $$
bs $$ cr
Nothing -> id
in render colwidth $ withHead $ prettyList $ map prettyBlock blocks
writeNative opts (Pandoc meta blocks) = do
let popts = defaultOutputOptionsNoColor{
outputOptionsIndentAmount = 2,
outputOptionsPageWidth = writerColumns opts,
outputOptionsCompact = True,
outputOptionsCompactParens = False,
outputOptionsStringStyle = Literal }
return $
case writerTemplate opts of
Just _ -> TL.toStrict $ pShowOpt popts (Pandoc meta blocks) <> "\n"
Nothing -> TL.toStrict $ pShowOpt popts blocks

View file

@ -146,7 +146,7 @@ tests pandocPath =
"dokuwiki_external_images.native" "dokuwiki_external_images.dokuwiki"
]
, testGroup "opml"
[ test' "basic" ["-r", "native", "-w", "opml", "--columns=78", "-s"]
[ test' "basic" ["-r", "native", "-w", "opml", "--columns=80", "-s"]
"testsuite.native" "writer.opml"
, test' "reader" ["-r", "opml", "-w", "native", "-s"]
"opml-reader.opml" "opml-reader.native"
@ -262,7 +262,7 @@ writerTests pandocPath format
"tables" opts "tables.native" ("tables" <.> format)
]
where
opts = ["-r", "native", "-w", format, "--columns=78",
opts = ["-r", "native", "-w", format, "--columns=80",
"--variable", "pandoc-version="]
extendedWriterTests :: FilePath -> String -> [TestTree]
@ -276,7 +276,7 @@ extendedWriterTests pandocPath format
("tables" </> name <.> format)
in map testForTable ["planets", "nordics", "students"]
where
opts = ["-r", "native", "-w", format, "--columns=78",
opts = ["-r", "native", "-w", format, "--columns=80",
"--variable", "pandoc-version="]
s5WriterTest :: FilePath -> String -> [String] -> String -> TestTree

View file

@ -3,7 +3,9 @@
\newcommand\foo{+}
Testing: $\mu\foo\eta$.
^D
[Para [Str "Testing:",Space,Math InlineMath "\\mu+\\eta",Str "."]]
[ Para
[ Str "Testing:", Space, Math InlineMath "\\mu+\\eta", Str "." ]
]
```
<!-- It would be nice to handle this case, but I don't

View file

@ -2,35 +2,35 @@
% pandoc -t native
[hi]{.smallcaps}
^D
[Para [SmallCaps [Str "hi"]]]
[ Para [ SmallCaps [ Str "hi" ] ] ]
```
```
% pandoc -t native
[hi]{style="font-variant: small-caps;"}
^D
[Para [SmallCaps [Str "hi"]]]
[ Para [ SmallCaps [ Str "hi" ] ] ]
```
```
% pandoc -t native
<span class="smallcaps">hi</span>
^D
[Para [SmallCaps [Str "hi"]]]
[ Para [ SmallCaps [ Str "hi" ] ] ]
```
```
% pandoc -f html -t native
<p><span class="smallcaps">hi</span></p>
^D
[Para [SmallCaps [Str "hi"]]]
[ Para [ SmallCaps [ Str "hi" ] ] ]
```
```
% pandoc -f html -t native
<p><span style="font-variant:small-caps">hi</span></p>
^D
[Para [SmallCaps [Str "hi"]]]
[ Para [ SmallCaps [ Str "hi" ] ] ]
```
```
@ -51,14 +51,24 @@
% pandoc -f html -t native
<bdo dir="ltr">foo</bdo>
^D
[Plain [Span ("",[],[("dir","ltr")]) [Str "foo"]]]
[ Plain [ Span ( "", [], [ ( "dir", "ltr" ) ] ) [ Str "foo" ] ] ]
```
```
% pandoc -f html -t native
<bdo dir="rtl">foo<bdo dir="ltr">bar</bdo>baz</bdo>
^D
[Plain [Span ("",[],[("dir","rtl")]) [Str "foo",Span ("",[],[("dir","ltr")]) [Str "bar"],Str "baz"]]]
[ Plain
[ Span
( "", [], [ ( "dir", "rtl" ) ] )
[ Str "foo"
, Span
( "", [], [ ( "dir", "ltr" ) ] )
[ Str "bar" ]
, Str "baz"
]
]
]
```
```
@ -66,5 +76,23 @@
<p><bdo dir="rtl">This text will go right
to left.</bdo></p>
^D
[Para [Span ("",[],[("dir","rtl")]) [Str "This",Space,Str "text",Space,Str "will",Space,Str "go",Space,Str "right",SoftBreak,Str "to",Space,Str "left."]]]
[ Para
[ Span
( "", [], [ ( "dir", "rtl" ) ] )
[ Str "This"
, Space
, Str "text"
, Space
, Str "will"
, Space
, Str "go"
, Space
, Str "right"
, SoftBreak
, Str "to"
, Space
, Str "left."
]
]
]
```

View file

@ -28,14 +28,183 @@ Triangles with sides of length \(a=p^2-q^2\), \(b=2pq\) and \(c=p^2+q^2\) are ri
These are all pretty interesting facts.
\end{remark}
^D
[Div ("def:tri",["definition"],[])
[Para [Strong [Str "Definition",Space,Str "1"],Space,Str "(right-angled",Space,Str "triangles).",Space,Space,Str "A",Space,Emph [Str "right-angled",Space,Str "triangle"],Space,Str "is",Space,Str "a",Space,Str "triangle",Space,Str "whose",Space,Str "sides",Space,Str "of",Space,Str "length\160",Math InlineMath "a",Str ",",Space,Math InlineMath "b",Space,Str "and\160",Math InlineMath "c",Str ",",Space,Str "in",Space,Str "some",Space,Str "permutation",Space,Str "of",Space,Str "order,",Space,Str "satisfies",Space,Math InlineMath "a^2+b^2=c^2",Str "."]]
,Div ("",["lemma"],[])
[Para [Strong [Str "Lemma",Space,Str "2"],Str ".",Space,Space,Emph [Str "The",Space,Str "triangle",Space,Str "with",Space,Str "sides",Space,Str "of",Space,Str "length\160",Math InlineMath "3",Str ",",Space,Math InlineMath "4",Space,Str "and\160",Math InlineMath "5",Space,Str "is",Space,Str "right-angled."]]]
,Div ("",["proof"],[])
[Para [Emph [Str "Proof."],Space,Str "This",Space,Str "lemma",Space,Str "follows",Space,Str "from",Space,Link ("",[],[("reference-type","ref"),("reference","def:tri")]) [Str "Definition\160\&1"] ("#def:tri",""),Space,Str "since",Space,Math InlineMath "3^2+4^2=9+16=25=5^2",Str ".",Str "\160\9723"]]
,Div ("thm:py",["theorem"],[])
[Para [Strong [Str "Theorem",Space,Str "3"],Space,Str "(Pythagorean",Space,Str "triplets).",Space,Space,Emph [Str "Triangles",Space,Str "with",Space,Str "sides",Space,Str "of",Space,Str "length",Space,Math InlineMath "a=p^2-q^2",Str ",",Space,Math InlineMath "b=2pq",Space,Str "and",Space,Math InlineMath "c=p^2+q^2",Space,Str "are",Space,Str "right-angled",Space,Str "triangles."]]]
,Div ("",["remark"],[])
[Para [Emph [Str "Remark",Space,Str "1"],Str ".",Space,Space,Str "These",Space,Str "are",Space,Str "all",Space,Str "pretty",Space,Str "interesting",Space,Str "facts."]]]
[ Div
( "def:tri", [ "definition" ], [] )
[ Para
[ Strong
[ Str "Definition", Space, Str "1" ]
, Space
, Str "(right-angled"
, Space
, Str "triangles)."
, Space
, Space
, Str "A"
, Space
, Emph
[ Str "right-angled", Space, Str "triangle" ]
, Space
, Str "is"
, Space
, Str "a"
, Space
, Str "triangle"
, Space
, Str "whose"
, Space
, Str "sides"
, Space
, Str "of"
, Space
, Str "length\160"
, Math InlineMath "a"
, Str ","
, Space
, Math InlineMath "b"
, Space
, Str "and\160"
, Math InlineMath "c"
, Str ","
, Space
, Str "in"
, Space
, Str "some"
, Space
, Str "permutation"
, Space
, Str "of"
, Space
, Str "order,"
, Space
, Str "satisfies"
, Space
, Math InlineMath "a^2+b^2=c^2"
, Str "."
]
]
, Div
( "", [ "lemma" ], [] )
[ Para
[ Strong
[ Str "Lemma", Space, Str "2" ]
, Str "."
, Space
, Space
, Emph
[ Str "The"
, Space
, Str "triangle"
, Space
, Str "with"
, Space
, Str "sides"
, Space
, Str "of"
, Space
, Str "length\160"
, Math InlineMath "3"
, Str ","
, Space
, Math InlineMath "4"
, Space
, Str "and\160"
, Math InlineMath "5"
, Space
, Str "is"
, Space
, Str "right-angled."
]
]
]
, Div
( "", [ "proof" ], [] )
[ Para
[ Emph
[ Str "Proof." ]
, Space
, Str "This"
, Space
, Str "lemma"
, Space
, Str "follows"
, Space
, Str "from"
, Space
, Link
( ""
, []
,
[ ( "reference-type", "ref" ), ( "reference", "def:tri" ) ]
)
[ Str "Definition\160\&1" ]
( "#def:tri", "" )
, Space
, Str "since"
, Space
, Math InlineMath "3^2+4^2=9+16=25=5^2"
, Str "."
, Str "\160\9723"
]
]
, Div
( "thm:py", [ "theorem" ], [] )
[ Para
[ Strong
[ Str "Theorem", Space, Str "3" ]
, Space
, Str "(Pythagorean"
, Space
, Str "triplets)."
, Space
, Space
, Emph
[ Str "Triangles"
, Space
, Str "with"
, Space
, Str "sides"
, Space
, Str "of"
, Space
, Str "length"
, Space
, Math InlineMath "a=p^2-q^2"
, Str ","
, Space
, Math InlineMath "b=2pq"
, Space
, Str "and"
, Space
, Math InlineMath "c=p^2+q^2"
, Space
, Str "are"
, Space
, Str "right-angled"
, Space
, Str "triangles."
]
]
]
, Div
( "", [ "remark" ], [] )
[ Para
[ Emph
[ Str "Remark", Space, Str "1" ]
, Str "."
, Space
, Space
, Str "These"
, Space
, Str "are"
, Space
, Str "all"
, Space
, Str "pretty"
, Space
, Str "interesting"
, Space
, Str "facts."
]
]
]
```

View file

@ -11,13 +11,25 @@ nested div
:::
:::::::::::::::::::::::::::::::
^D
[Div ("",["warning"],[])
[Para [Str "This",Space,Str "is",Space,Str "the",Space,Str "warning!"]
,OrderedList (1,Decimal,Period)
[[Plain [Str "list"]]
,[Plain [Str "another"]]]
,Div ("myid",["class"],[("key","val")])
[Para [Str "nested",Space,Str "div"]]]]
[ Div
( "", [ "warning" ], [] )
[ Para
[ Str "This"
, Space
, Str "is"
, Space
, Str "the"
, Space
, Str "warning!"
]
, OrderedList
( 1, Decimal, Period )
[ [ Plain [ Str "list" ] ], [ Plain [ Str "another" ] ] ]
, Div
( "myid", [ "class" ], [ ( "key", "val" ) ] )
[ Para [ Str "nested", Space, Str "div" ] ]
]
]
```
```
@ -26,7 +38,7 @@ foo
:::
bar
^D
[Para [Str "foo",SoftBreak,Str ":::",SoftBreak,Str "bar"]]
[ Para [ Str "foo", SoftBreak, Str ":::", SoftBreak, Str "bar" ] ]
```
```
@ -37,7 +49,19 @@ Here is a paragraph.
And another.
:::::
^D
[Div ("",["Warning"],[])
[Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "paragraph."]
,Para [Str "And",Space,Str "another."]]]
[ Div
( "", [ "Warning" ], [] )
[ Para
[ Str "Here"
, Space
, Str "is"
, Space
, Str "a"
, Space
, Str "paragraph."
]
, Para
[ Str "And", Space, Str "another." ]
]
]
```

View file

@ -7,5 +7,11 @@ Note[^1].
[^2]: the second, unused, note.
^D
[WARNING] Note with key '2' defined at line 5 column 1 but not used.
[Para [Str "Note",Note [Para [Str "the",Space,Str "first",Space,Str "note."]],Str "."]]
[ Para
[ Str "Note"
, Note
[ Para [ Str "the", Space, Str "first", Space, Str "note." ] ]
, Str "."
]
]
```

View file

@ -2,5 +2,5 @@
% pandoc -f latex+raw_tex -t native
\noindent hi
^D
[Para [RawInline (Format "latex") "\\noindent ",Str "hi"]]
[ Para [ RawInline ( Format "latex" ) "\\noindent ", Str "hi" ] ]
```

View file

@ -20,35 +20,88 @@
</tbody>
</table>
^D
[Table ("",[],[]) (Caption Nothing
[Plain [Str "Demonstration",Space,Str "of",Space,Str "simple",Space,Str "table",Space,Str "syntax."]])
[(AlignRight,ColWidthDefault)
,(AlignLeft,ColWidthDefault)
,(AlignCenter,ColWidthDefault)
,(AlignDefault,ColWidthDefault)]
(TableHead ("",[],[])
[Row ("",["header"],[])
[Cell ("",[],[]) AlignRight (RowSpan 1) (ColSpan 1)
[Plain [Str "Right"]]
,Cell ("",[],[]) AlignLeft (RowSpan 1) (ColSpan 1)
[Plain [Str "Left"]]
,Cell ("",[],[]) AlignCenter (RowSpan 1) (ColSpan 1)
[Plain [Str "Center"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Default"]]]])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",["odd"],[])
[Cell ("",[],[]) AlignRight (RowSpan 1) (ColSpan 1)
[Plain [Str "12"]]
,Cell ("",[],[]) AlignLeft (RowSpan 1) (ColSpan 1)
[Plain [Str "12"]]
,Cell ("",[],[]) AlignCenter (RowSpan 1) (ColSpan 1)
[Plain [Str "12"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "12"]]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing
[ Plain
[ Str "Demonstration"
, Space
, Str "of"
, Space
, Str "simple"
, Space
, Str "table"
, Space
, Str "syntax."
]
]
)
[
( AlignRight, ColWidthDefault )
,
( AlignLeft, ColWidthDefault )
,
( AlignCenter, ColWidthDefault )
,
( AlignDefault, ColWidthDefault )
]
( TableHead
( "", [], [] )
[ Row
( "", [ "header" ], [] )
[ Cell
( "", [], [] ) AlignRight
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Right" ] ]
, Cell
( "", [], [] ) AlignLeft
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Left" ] ]
, Cell
( "", [], [] ) AlignCenter
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Center" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Default" ] ]
]
]
)
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [ "odd" ], [] )
[ Cell
( "", [], [] ) AlignRight
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "12" ] ]
, Cell
( "", [], [] ) AlignLeft
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "12" ] ]
, Cell
( "", [], [] ) AlignCenter
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "12" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "12" ] ]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```
```
@ -62,26 +115,48 @@
</tr>
</table>
^D
[Table ("",[],[]) (Caption Nothing
[])
[(AlignRight,ColWidthDefault)
,(AlignLeft,ColWidthDefault)
,(AlignCenter,ColWidthDefault)
,(AlignRight,ColWidthDefault)]
(TableHead ("",[],[])
[])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",["odd"],[])
[Cell ("",[],[]) AlignRight (RowSpan 1) (ColSpan 1)
[Plain [Str "12"]]
,Cell ("",[],[]) AlignLeft (RowSpan 1) (ColSpan 1)
[Plain [Str "12"]]
,Cell ("",[],[]) AlignCenter (RowSpan 1) (ColSpan 1)
[Plain [Str "12"]]
,Cell ("",[],[]) AlignRight (RowSpan 1) (ColSpan 1)
[Plain [Str "12"]]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [] )
[
( AlignRight, ColWidthDefault )
,
( AlignLeft, ColWidthDefault )
,
( AlignCenter, ColWidthDefault )
,
( AlignRight, ColWidthDefault )
]
( TableHead ( "", [], [] ) [] )
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [ "odd" ], [] )
[ Cell
( "", [], [] ) AlignRight
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "12" ] ]
, Cell
( "", [], [] ) AlignLeft
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "12" ] ]
, Cell
( "", [], [] ) AlignCenter
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "12" ] ]
, Cell
( "", [], [] ) AlignRight
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "12" ] ]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```

View file

@ -7,5 +7,11 @@
\label{fig:setminus}
\end{figure}
^D
[Para [Image ("fig:setminus",[],[("width","80%")]) [Str "Set",Space,Str "subtraction"] ("setminus.png","fig:")]]
[ Para
[ Image
( "fig:setminus", [], [ ( "width", "80%" ) ] )
[ Str "Set", Space, Str "subtraction" ]
( "setminus.png", "fig:" )
]
]
```

View file

@ -4,7 +4,7 @@
\section{A section}\label{foo}
}
^D
[Header 1 ("foo",[],[]) [Str "A",Space,Str "section"]]
[ Header 1 ( "foo", [], [] ) [ Str "A", Space, Str "section" ] ]
```
```
@ -13,15 +13,17 @@
\section{A section}\label{foo}
}
^D
[Div ("bar",[],[])
[Header 1 ("foo",[],[]) [Str "A",Space,Str "section"]]]
[ Div
( "bar", [], [] )
[ Header 1 ( "foo", [], [] ) [ Str "A", Space, Str "section" ] ]
]
```
```
% pandoc -f latex -t native
Bar \hypertarget{foo}{Foo}
^D
[Para [Str "Bar",Space,Span ("foo",[],[]) [Str "Foo"]]]
[ Para [ Str "Bar", Space, Span ( "foo", [], [] ) [ Str "Foo" ] ] ]
```
```
@ -32,7 +34,6 @@ bar
\end{verbatim}
}
^D
[Div ("foo",[],[])
[CodeBlock ("",[],[]) "bar"]]
[ Div ( "foo", [], [] ) [ CodeBlock ( "", [], [] ) "bar" ] ]
```

View file

@ -2,11 +2,41 @@
% pandoc --abbreviations=command/abbrevs -t native
Foo. bar baz h.k. and e.g. and Mr. Brown.
^D
[Para [Str "Foo.\160bar",Space,Str "baz",Space,Str "h.k.\160and",Space,Str "e.g.",Space,Str "and",Space,Str "Mr.",Space,Str "Brown."]]
[ Para
[ Str "Foo.\160bar"
, Space
, Str "baz"
, Space
, Str "h.k.\160and"
, Space
, Str "e.g."
, Space
, Str "and"
, Space
, Str "Mr."
, Space
, Str "Brown."
]
]
```
```
% pandoc -t native
Foo. bar baz h.k. and e.g. and Mr. Brown.
^D
[Para [Str "Foo.",Space,Str "bar",Space,Str "baz",Space,Str "h.k.",Space,Str "and",Space,Str "e.g.\160and",Space,Str "Mr.\160Brown."]]
[ Para
[ Str "Foo."
, Space
, Str "bar"
, Space
, Str "baz"
, Space
, Str "h.k."
, Space
, Str "and"
, Space
, Str "e.g.\160and"
, Space
, Str "Mr.\160Brown."
]
]
```

View file

@ -8,6 +8,8 @@ C&=&D,\\
E&=&F
\end{eqnarray}
^D
[Para [Math DisplayMath "\\begin{aligned}\nA&=&B,\\\\\nC&=&D,\\\\\n%\\end{eqnarray}\n%\\begin{eqnarray}\nE&=&F\\end{aligned}"]]
[ Para
[ Math DisplayMath "\\begin{aligned}\nA&=&B,\\\\\nC&=&D,\\\\\n%\\end{eqnarray}\n%\\begin{eqnarray}\nE&=&F\\end{aligned}" ]
]
```

View file

@ -2,12 +2,14 @@
% pandoc -f markdown -t native
<?php echo "1" ; ?>
^D
[RawBlock (Format "html") "<?php echo \"1\" ; ?>"]
[ RawBlock ( Format "html" ) "<?php echo \"1\" ; ?>" ]
```
```
% pandoc -f markdown -t native
a<?php echo "1" ; ?>
^D
[Para [Str "a",RawInline (Format "html") "<?php echo \"1\" ; ?>"]]
[ Para
[ Str "a", RawInline ( Format "html" ) "<?php echo \"1\" ; ?>" ]
]
```

View file

@ -5,5 +5,17 @@
\includegraphics[width=17cm]{\mycolor /header}
Magnificent \mycolor{} header.
^D
[Para [Image ("",[],[("width","17cm")]) [Str "image"] ("red/header",""),SoftBreak,Str "Magnificent",Space,Str "red",Space,Str "header."]]
[ Para
[ Image
( "", [], [ ( "width", "17cm" ) ] )
[ Str "image" ]
( "red/header", "" )
, SoftBreak
, Str "Magnificent"
, Space
, Str "red"
, Space
, Str "header."
]
]
```

View file

@ -2,12 +2,12 @@
% pandoc -t native
(i<j)
^D
[Para [Str "(i<j)"]]
[ Para [ Str "(i<j)" ] ]
```
```
% pandoc -t native
i<j-1, j>k
^D
[Para [Str "i<j-1,",Space,Str "j>k"]]
[ Para [ Str "i<j-1,", Space, Str "j>k" ] ]
```

View file

@ -7,24 +7,61 @@
line of text
----- ------------------------------------------------
^D
[Table ("",[],[]) (Caption Nothing
[])
[(AlignRight,ColWidth 8.333333333333333e-2)
,(AlignLeft,ColWidth 0.6805555555555556)]
(TableHead ("",[],[])
[])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "foo"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "bar"]]]
,Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "foo"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "this",Space,Str "is",Space,Str "a",Space,Str "long",SoftBreak,Str "line",Space,Str "of",Space,Str "text"]]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [] )
[
( AlignRight, ColWidth 8.333333333333333 e- 2 )
,
( AlignLeft, ColWidth 0.6805555555555556 )
]
( TableHead ( "", [], [] ) [] )
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "foo" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "bar" ] ]
]
, Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "foo" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain
[ Str "this"
, Space
, Str "is"
, Space
, Str "a"
, Space
, Str "long"
, SoftBreak
, Str "line"
, Space
, Str "of"
, Space
, Str "text"
]
]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```

View file

@ -5,7 +5,7 @@ See #3401 and <http://orgmode.org/manual/Macro-replacement.html>
#+MACRO: HELLO /Hello, $1/
{{{HELLO(World)}}}
^D
[Para [Emph [Str "Hello,",Space,Str "World"]]]
[ Para [ Emph [ Str "Hello,", Space, Str "World" ] ] ]
```
Inverted argument order
@ -15,5 +15,5 @@ Inverted argument order
#+MACRO: A $2,$1
{{{A(1,2)}}}
^D
[Para [Str "2,1"]]
[ Para [ Str "2,1" ] ]
```

View file

@ -9,5 +9,7 @@
% pandoc -f rst -t native
:foo:`text`
^D
[Para [Code ("",["interpreted-text"],[("role","foo")]) "text"]]
[ Para
[ Code ( "", [ "interpreted-text" ], [ ( "role", "foo" ) ] ) "text" ]
]
```

View file

@ -10,11 +10,20 @@ Text
More text
^D
[Para [Str "Text"]
,Header 1 ("subsection",[],[]) [Str "Subsection"]
,Para [Str "Included",Space,Str "text"]
,Plain [Str "Lorem",Space,Str "ipsum."]
,CodeBlock ("",["haskell"],[]) "putStrLn outString\n"
,RawBlock (Format "latex") "\\emph{Hello}"
,Para [Str "More",Space,Str "text"]]
[ Para
[ Str "Text" ]
, Header 1
( "subsection", [], [] )
[ Str "Subsection" ]
, Para
[ Str "Included", Space, Str "text" ]
, Plain
[ Str "Lorem", Space, Str "ipsum." ]
, CodeBlock
( "", [ "haskell" ], [] ) "putStrLn outString\n"
, RawBlock
( Format "latex" ) "\\emph{Hello}"
, Para
[ Str "More", Space, Str "text" ]
]
```

View file

@ -10,16 +10,22 @@
not continuation
^D
[BulletList
[[Plain [Str "a"]
,BulletList
[[Plain [Str "b"]
,BulletList
[[Plain [Str "c"]]]]]]
,[CodeBlock ("",[],[]) "code"]]
,OrderedList (1000,Decimal,Period)
[[Plain [Str "one"]]]
,CodeBlock ("",[],[]) "not continuation"]
[ BulletList
[
[ Plain
[ Str "a" ]
, BulletList
[ [ Plain [ Str "b" ], BulletList [ [ Plain [ Str "c" ] ] ] ] ]
]
,
[ CodeBlock ( "", [], [] ) "code" ]
]
, OrderedList
( 1000, Decimal, Period )
[ [ Plain [ Str "one" ] ] ]
, CodeBlock
( "", [], [] ) "not continuation"
]
```
```
@ -34,13 +40,16 @@
continuation
^D
[BulletList
[[Plain [Str "a"]]
,[Plain [Str "b"]
,BulletList
[[Plain [Str "c"]]]]
,[CodeBlock ("",[],[]) "not code"]]
,OrderedList (1000,Decimal,Period)
[[Para [Str "one"]
,Para [Str "continuation"]]]]
[ BulletList
[
[ Plain [ Str "a" ] ]
,
[ Plain [ Str "b" ], BulletList [ [ Plain [ Str "c" ] ] ] ]
,
[ CodeBlock ( "", [], [] ) "not code" ]
]
, OrderedList
( 1000, Decimal, Period )
[ [ Para [ Str "one" ], Para [ Str "continuation" ] ] ]
]
```

View file

@ -24,26 +24,46 @@ on Windows builds.
| | |
+---+---+
^D
[Table ("",[],[]) (Caption Nothing
[])
[(AlignDefault,ColWidth 5.555555555555555e-2)
,(AlignDefault,ColWidth 5.555555555555555e-2)]
(TableHead ("",[],[])
[])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "1"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "2"]]]
,Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [] )
[
( AlignDefault, ColWidth 5.555555555555555 e- 2 )
,
( AlignDefault, ColWidth 5.555555555555555 e- 2 )
]
( TableHead ( "", [], [] ) [] )
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "1" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "2" ] ]
]
, Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 ) []
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 ) []
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```
```

View file

@ -3,10 +3,53 @@
\subfile{command/sub-file-chapter-1}
\subfile{command/sub-file-chapter-2}
^D
[Header 1 ("chapter-1",[],[]) [Str "Chapter",Space,Str "1"]
,Para [Str "This",Space,Str "is",Space,Str "Chapter",Space,Str "1,",Space,Str "provided",Space,Str "in",Space,Str "a",Space,Str "sub",Space,Str "file."]
,Header 1 ("chapter-2",[],[]) [Str "Chapter",Space,Str "2"]
,Para [Str "This",Space,Str "is",Space,Str "Chapter",Space,Str "2,",Space,Str "provided",Space,Str "in",Space,Str "a",Space,Str "second",Space,Str "sub",Space,Str "file."]]
[ Header 1
( "chapter-1", [], [] )
[ Str "Chapter", Space, Str "1" ]
, Para
[ Str "This"
, Space
, Str "is"
, Space
, Str "Chapter"
, Space
, Str "1,"
, Space
, Str "provided"
, Space
, Str "in"
, Space
, Str "a"
, Space
, Str "sub"
, Space
, Str "file."
]
, Header 1
( "chapter-2", [], [] )
[ Str "Chapter", Space, Str "2" ]
, Para
[ Str "This"
, Space
, Str "is"
, Space
, Str "Chapter"
, Space
, Str "2,"
, Space
, Str "provided"
, Space
, Str "in"
, Space
, Str "a"
, Space
, Str "second"
, Space
, Str "sub"
, Space
, Str "file."
]
]
```
```
@ -14,6 +57,9 @@
\subfile{command/sub-file-chapter-1}
\subfile{command/sub-file-chapter-2}
^D
[RawBlock (Format "latex") "\\subfile{command/sub-file-chapter-1}"
,RawBlock (Format "latex") "\\subfile{command/sub-file-chapter-2}"]
[ RawBlock
( Format "latex" ) "\\subfile{command/sub-file-chapter-1}"
, RawBlock
( Format "latex" ) "\\subfile{command/sub-file-chapter-2}"
]
```

View file

@ -5,37 +5,108 @@
:header: Flavor,Price,Slogan
:file: command/3533-rst-csv-tables.csv
^D
[Table ("",[],[]) (Caption Nothing
[Plain [Str "Test"]])
[(AlignDefault,ColWidth 0.4)
,(AlignDefault,ColWidth 0.2)
,(AlignDefault,ColWidth 0.4)]
(TableHead ("",[],[])
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Flavor"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Price"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Slogan"]]]])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Albatross"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "2.99"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "On",Space,Str "a",Space,Str "stick!"]]]
,Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Crunchy",Space,Str "Frog"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "1.49"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "If",Space,Str "we",Space,Str "took",Space,Str "the",Space,Str "bones",Space,Str "out,",Space,Str "it",Space,Str "wouldn't",Space,Str "be",SoftBreak,Str "crunchy,",Space,Str "now",Space,Str "would",Space,Str "it?"]]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [ Plain [ Str "Test" ] ] )
[
( AlignDefault, ColWidth 0.4 )
,
( AlignDefault, ColWidth 0.2 )
,
( AlignDefault, ColWidth 0.4 )
]
( TableHead
( "", [], [] )
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Flavor" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Price" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Slogan" ] ]
]
]
)
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Albatross" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "2.99" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "On", Space, Str "a", Space, Str "stick!" ] ]
]
, Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Crunchy", Space, Str "Frog" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "1.49" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain
[ Str "If"
, Space
, Str "we"
, Space
, Str "took"
, Space
, Str "the"
, Space
, Str "bones"
, Space
, Str "out,"
, Space
, Str "it"
, Space
, Str "wouldn't"
, Space
, Str "be"
, SoftBreak
, Str "crunchy,"
, Space
, Str "now"
, Space
, Str "would"
, Space
, Str "it?"
]
]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```
```
@ -49,37 +120,80 @@
'cat''s' 3 4
'dog''s' 2 3
^D
[Table ("",[],[]) (Caption Nothing
[Plain [Str "Test"]])
[(AlignDefault,ColWidthDefault)
,(AlignDefault,ColWidthDefault)
,(AlignDefault,ColWidthDefault)]
(TableHead ("",[],[])
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "a"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "b"]]]])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "cat's"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "3"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "4"]]]
,Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "dog's"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "2"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "3"]]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [ Plain [ Str "Test" ] ] )
[
( AlignDefault, ColWidthDefault )
,
( AlignDefault, ColWidthDefault )
,
( AlignDefault, ColWidthDefault )
]
( TableHead
( "", [], [] )
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 ) []
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "a" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "b" ] ]
]
]
)
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "cat's" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "3" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "4" ] ]
]
, Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "dog's" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "2" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "3" ] ]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```
```
@ -89,20 +203,34 @@
"1","\""
^D
[Table ("",[],[]) (Caption Nothing
[Plain [Str "Test"]])
[(AlignDefault,ColWidthDefault)
,(AlignDefault,ColWidthDefault)]
(TableHead ("",[],[])
[])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "1"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "\""]]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [ Plain [ Str "Test" ] ] )
[
( AlignDefault, ColWidthDefault )
,
( AlignDefault, ColWidthDefault )
]
( TableHead ( "", [], [] ) [] )
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "1" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "\"" ] ]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```

View file

@ -18,7 +18,26 @@ I want to explain the interface of \lstinline{public class MyClass}.
% pandoc -f latex -t native
I want to explain the interface of \lstinline[language=Java]{public class MyClass}.
^D
[Para [Str "I",Space,Str "want",Space,Str "to",Space,Str "explain",Space,Str "the",Space,Str "interface",Space,Str "of",Space,Code ("",["java"],[]) "public class MyClass",Str "."]]
[ Para
[ Str "I"
, Space
, Str "want"
, Space
, Str "to"
, Space
, Str "explain"
, Space
, Str "the"
, Space
, Str "interface"
, Space
, Str "of"
, Space
, Code
( "", [ "java" ], [] ) "public class MyClass"
, Str "."
]
]
```
```
@ -41,5 +60,24 @@ I want to explain the interface of \mintinline{java}|public class MyClass|.
% pandoc -f latex -t native
I want to explain the interface of \mintinline[linenos]{java}{public class MyClass}.
^D
[Para [Str "I",Space,Str "want",Space,Str "to",Space,Str "explain",Space,Str "the",Space,Str "interface",Space,Str "of",Space,Code ("",["java"],[]) "public class MyClass",Str "."]]
[ Para
[ Str "I"
, Space
, Str "want"
, Space
, Str "to"
, Space
, Str "explain"
, Space
, Str "the"
, Space
, Str "interface"
, Space
, Str "of"
, Space
, Code
( "", [ "java" ], [] ) "public class MyClass"
, Str "."
]
]
```

View file

@ -7,14 +7,14 @@ Generalized raw attributes.
foo bar
```
^D
[RawBlock (Format "ms") ".MACRO\nfoo bar"]
[ RawBlock ( Format "ms" ) ".MACRO\nfoo bar" ]
````
````
% pandoc -t native
Hi `there`{=ms}.
^D
[Para [Str "Hi",Space,RawInline (Format "ms") "there",Str "."]]
[ Para [ Str "Hi", Space, RawInline ( Format "ms" ) "there", Str "." ] ]
````
````
@ -24,5 +24,5 @@ Hi `there`{=ms}.
foo bar
~~~
^D
[RawBlock (Format "ms") ".MACRO\nfoo bar"]
[ RawBlock ( Format "ms" ) ".MACRO\nfoo bar" ]
````

View file

@ -4,35 +4,231 @@
% pandoc -f latex -t native
Many programming languages provide \glspl{API}. Each \gls{API} should provide a documentation.
^D
[Para [Str "Many",Space,Str "programming",Space,Str "languages",Space,Str "provide",Space,Span ("",[],[("acronym-label","API"),("acronym-form","plural+short")]) [Str "APIs"],Str ".",Space,Str "Each",Space,Span ("",[],[("acronym-label","API"),("acronym-form","singular+short")]) [Str "API"],Space,Str "should",Space,Str "provide",Space,Str "a",Space,Str "documentation."]]
[ Para
[ Str "Many"
, Space
, Str "programming"
, Space
, Str "languages"
, Space
, Str "provide"
, Space
, Span
( ""
, []
,
[ ( "acronym-label", "API" ), ( "acronym-form", "plural+short" ) ]
)
[ Str "APIs" ]
, Str "."
, Space
, Str "Each"
, Space
, Span
( ""
, []
,
[
( "acronym-label", "API" )
,
( "acronym-form", "singular+short" )
]
)
[ Str "API" ]
, Space
, Str "should"
, Space
, Str "provide"
, Space
, Str "a"
, Space
, Str "documentation."
]
]
```
```
% pandoc -f latex -t native
\Glsdesc{API} XYZ ist not as performant as \glsdesc{API} ZXY.
^D
[Para [Span ("",[],[("acronym-label","API"),("acronym-form","singular+long")]) [Str "API"],Space,Str "XYZ",Space,Str "ist",Space,Str "not",Space,Str "as",Space,Str "performant",Space,Str "as",Space,Span ("",[],[("acronym-label","API"),("acronym-form","singular+long")]) [Str "API"],Space,Str "ZXY."]]
[ Para
[ Span
( ""
, []
,
[
( "acronym-label", "API" )
,
( "acronym-form", "singular+long" )
]
)
[ Str "API" ]
, Space
, Str "XYZ"
, Space
, Str "ist"
, Space
, Str "not"
, Space
, Str "as"
, Space
, Str "performant"
, Space
, Str "as"
, Space
, Span
( ""
, []
,
[
( "acronym-label", "API" )
,
( "acronym-form", "singular+long" )
]
)
[ Str "API" ]
, Space
, Str "ZXY."
]
]
```
```
% pandoc -f latex -t native
\Acrlong{API} XYZ ist not as performant as \acrlong{API} ZXY.
^D
[Para [Span ("",[],[("acronym-label","API"),("acronym-form","singular+long")]) [Str "API"],Space,Str "XYZ",Space,Str "ist",Space,Str "not",Space,Str "as",Space,Str "performant",Space,Str "as",Space,Span ("",[],[("acronym-label","API"),("acronym-form","singular+long")]) [Str "API"],Space,Str "ZXY."]]
[ Para
[ Span
( ""
, []
,
[
( "acronym-label", "API" )
,
( "acronym-form", "singular+long" )
]
)
[ Str "API" ]
, Space
, Str "XYZ"
, Space
, Str "ist"
, Space
, Str "not"
, Space
, Str "as"
, Space
, Str "performant"
, Space
, Str "as"
, Space
, Span
( ""
, []
,
[
( "acronym-label", "API" )
,
( "acronym-form", "singular+long" )
]
)
[ Str "API" ]
, Space
, Str "ZXY."
]
]
```
```
% pandoc -f latex -t native
\Acrfull{API} XYZ ist not as performant as \acrfull{API} ZXY.
^D
[Para [Span ("",[],[("acronym-label","API"),("acronym-form","singular+full")]) [Str "API"],Space,Str "XYZ",Space,Str "ist",Space,Str "not",Space,Str "as",Space,Str "performant",Space,Str "as",Space,Span ("",[],[("acronym-label","API"),("acronym-form","singular+full")]) [Str "API"],Space,Str "ZXY."]]
[ Para
[ Span
( ""
, []
,
[
( "acronym-label", "API" )
,
( "acronym-form", "singular+full" )
]
)
[ Str "API" ]
, Space
, Str "XYZ"
, Space
, Str "ist"
, Space
, Str "not"
, Space
, Str "as"
, Space
, Str "performant"
, Space
, Str "as"
, Space
, Span
( ""
, []
,
[
( "acronym-label", "API" )
,
( "acronym-form", "singular+full" )
]
)
[ Str "API" ]
, Space
, Str "ZXY."
]
]
```
```
% pandoc -f latex -t native
\Acrshort{API} XYZ ist not as performant as \acrshort{API} ZXY.
^D
[Para [Span ("",[],[("acronym-label","API"),("acronym-form","singular+abbrv")]) [Str "API"],Space,Str "XYZ",Space,Str "ist",Space,Str "not",Space,Str "as",Space,Str "performant",Space,Str "as",Space,Span ("",[],[("acronym-label","API"),("acronym-form","singular+abbrv")]) [Str "API"],Space,Str "ZXY."]]
[ Para
[ Span
( ""
, []
,
[
( "acronym-label", "API" )
,
( "acronym-form", "singular+abbrv" )
]
)
[ Str "API" ]
, Space
, Str "XYZ"
, Space
, Str "ist"
, Space
, Str "not"
, Space
, Str "as"
, Space
, Str "performant"
, Space
, Str "as"
, Space
, Span
( ""
, []
,
[
( "acronym-label", "API" )
,
( "acronym-form", "singular+abbrv" )
]
)
[ Str "API" ]
, Space
, Str "ZXY."
]
]
```
# Commands of [acronym package](ftp://ftp.mpi-sb.mpg.de/pub/tex/mirror/ftp.dante.de/pub/tex/macros/latex/contrib/acronym/acronym.pdf)
@ -41,5 +237,45 @@ Many programming languages provide \glspl{API}. Each \gls{API} should provide a
% pandoc -f latex -t native
Many programming languages provide \acp{API}. Each \ac{API} should provide a documentation.
^D
[Para [Str "Many",Space,Str "programming",Space,Str "languages",Space,Str "provide",Space,Span ("",[],[("acronym-label","API"),("acronym-form","plural+short")]) [Str "APIs"],Str ".",Space,Str "Each",Space,Span ("",[],[("acronym-label","API"),("acronym-form","singular+short")]) [Str "API"],Space,Str "should",Space,Str "provide",Space,Str "a",Space,Str "documentation."]]
[ Para
[ Str "Many"
, Space
, Str "programming"
, Space
, Str "languages"
, Space
, Str "provide"
, Space
, Span
( ""
, []
,
[ ( "acronym-label", "API" ), ( "acronym-form", "plural+short" ) ]
)
[ Str "APIs" ]
, Str "."
, Space
, Str "Each"
, Space
, Span
( ""
, []
,
[
( "acronym-label", "API" )
,
( "acronym-form", "singular+short" )
]
)
[ Str "API" ]
, Space
, Str "should"
, Space
, Str "provide"
, Space
, Str "a"
, Space
, Str "documentation."
]
]
```

View file

@ -6,7 +6,11 @@ hello
\endmulti
^D
[RawBlock (Format "tex") "\\multi"
,Para [Str "hello"]
,RawBlock (Format "tex") "\\endmulti"]
[ RawBlock
( Format "tex" ) "\\multi"
, Para
[ Str "hello" ]
, RawBlock
( Format "tex" ) "\\endmulti"
]
```

View file

@ -4,13 +4,35 @@
Same but bzip2 it and nice it <tt>zfs send tank/storage/data/svn@daily-2014-03-20_00.00.00--2w | nice -15 bzip2 | ssh user@hyper.somewhere.org "> /storage/c-3po/tank-storage-data-svn.dmp.bz2"</tt>
^D
[Para [Quoted DoubleQuote [Str "Hello"]]
,Para [Str "Same",Space,Str "but",Space,Str "bzip2",Space,Str "it",Space,Str "and",Space,Str "nice",Space,Str "it",Space,Code ("",[],[]) "zfs send tank/storage/data/svn@daily-2014-03-20_00.00.00--2w | nice -15 bzip2 | ssh user@hyper.somewhere.org \"> /storage/c-3po/tank-storage-data-svn.dmp.bz2\""]]
[ Para
[ Quoted DoubleQuote [ Str "Hello" ] ]
, Para
[ Str "Same"
, Space
, Str "but"
, Space
, Str "bzip2"
, Space
, Str "it"
, Space
, Str "and"
, Space
, Str "nice"
, Space
, Str "it"
, Space
, Code
( ""
, []
, []
) "zfs send tank/storage/data/svn@daily-2014-03-20_00.00.00--2w | nice -15 bzip2 | ssh user@hyper.somewhere.org \"> /storage/c-3po/tank-storage-data-svn.dmp.bz2\""
]
]
```
```
% pandoc -f mediawiki -t native
"Hello"
^D
[Para [Str "\"Hello\""]]
[ Para [ Str "\"Hello\"" ] ]
```

View file

@ -2,14 +2,36 @@
% pandoc -f latex -t native
\SI[round-precision=2]{1}{m} is equal to \SI{1000}{mm}
^D
[Para [Str "1\160m",Space,Str "is",Space,Str "equal",Space,Str "to",Space,Str "1000\160mm"]]
[ Para
[ Str "1\160m"
, Space
, Str "is"
, Space
, Str "equal"
, Space
, Str "to"
, Space
, Str "1000\160mm"
]
]
```
```
% pandoc -f latex -t native
\SI[round-precision=2]{1}[\$]{} is equal to \SI{0.938094}{\euro}
^D
[Para [Str "$\160\&1",Space,Str "is",Space,Str "equal",Space,Str "to",Space,Str "0.938094\160\8364"]]
[ Para
[ Str "$\160\&1"
, Space
, Str "is"
, Space
, Str "equal"
, Space
, Str "to"
, Space
, Str "0.938094\160\8364"
]
]
```
@ -17,35 +39,35 @@
% pandoc -f latex -t native
\SI{30}{\milli\meter}
^D
[Para [Str "30\160mm"]]
[ Para [ Str "30\160mm" ] ]
```
```
% pandoc -f latex -t native
\SI{6}{\gram}
^D
[Para [Str "6\160g"]]
[ Para [ Str "6\160g" ] ]
```
```
% pandoc -f latex -t native
\SI{25}{\square\meter}
^D
[Para [Str "25\160m",Superscript [Str "2"]]]
[ Para [ Str "25\160m", Superscript [ Str "2" ] ] ]
```
```
% pandoc -f latex -t native
\SI{18.2}{\degreeCelsius}
^D
[Para [Str "18.2\160\176C"]]
[ Para [ Str "18.2\160\176C" ] ]
```
```
% pandoc -f latex -t native
\SI{18.2}{\celsius}
^D
[Para [Str "18.2\160\176C"]]
[ Para [ Str "18.2\160\176C" ] ]
```
# SIrange tests
@ -56,19 +78,19 @@
% pandoc -f latex -t native
\SIrange{10}{20}{\gram}
^D
[Para [Str "10\160g\8211\&20\160g"]]
[ Para [ Str "10\160g\8211\&20\160g" ] ]
```
```
% pandoc -f latex -t native
\SIrange{35}{9}{\milli\meter}
^D
[Para [Str "35\160mm\8211\&9\160mm"]]
[ Para [ Str "35\160mm\8211\&9\160mm" ] ]
```
```
% pandoc -f latex -t native
\SIrange{4}{97367265}{\celsius}
^D
[Para [Str "4\160\176C\8211\&97367265\160\176C"]]
[ Para [ Str "4\160\176C\8211\&97367265\160\176C" ] ]
```
## Decimal range with simple units
@ -77,7 +99,7 @@
% pandoc -f latex -t native
\SIrange{4.5}{97367265.5}{\celsius}
^D
[Para [Str "4.5\160\176C\8211\&97367265.5\160\176C"]]
[ Para [ Str "4.5\160\176C\8211\&97367265.5\160\176C" ] ]
```
## Squared, cubed etc. units
@ -86,21 +108,45 @@
% pandoc -f latex -t native
\SIrange{10}{20}{\square\meter}
^D
[Para [Str "10\160m",Superscript [Str "2"],Str "\8211\&20\160m",Superscript [Str "2"]]]
[ Para
[ Str "10\160m"
, Superscript
[ Str "2" ]
, Str "\8211\&20\160m"
, Superscript
[ Str "2" ]
]
]
```
```
% pandoc -f latex -t native
\SIrange{10}{20}{\cubic\meter}
^D
[Para [Str "10\160m",Superscript [Str "3"],Str "\8211\&20\160m",Superscript [Str "3"]]]
[ Para
[ Str "10\160m"
, Superscript
[ Str "3" ]
, Str "\8211\&20\160m"
, Superscript
[ Str "3" ]
]
]
```
```
% pandoc -f latex -t native
\SIrange{10}{20}{\raisetothe{4}\meter}
^D
[Para [Str "10\160m",Superscript [Str "4"],Str "\8211\&20\160m",Superscript [Str "4"]]]
[ Para
[ Str "10\160m"
, Superscript
[ Str "4" ]
, Str "\8211\&20\160m"
, Superscript
[ Str "4" ]
]
]
```
@ -108,21 +154,45 @@
% pandoc -f latex -t native
\SIrange{10}{20}{\meter\squared}
^D
[Para [Str "10\160m",Superscript [Str "2"],Str "\8211\&20\160m",Superscript [Str "2"]]]
[ Para
[ Str "10\160m"
, Superscript
[ Str "2" ]
, Str "\8211\&20\160m"
, Superscript
[ Str "2" ]
]
]
```
```
% pandoc -f latex -t native
\SIrange{10}{20}{\meter\cubed}
^D
[Para [Str "10\160m",Superscript [Str "3"],Str "\8211\&20\160m",Superscript [Str "3"]]]
[ Para
[ Str "10\160m"
, Superscript
[ Str "3" ]
, Str "\8211\&20\160m"
, Superscript
[ Str "3" ]
]
]
```
```
% pandoc -f latex -t native
\SIrange{10}{20}{\meter\tothe{4}}
^D
[Para [Str "10\160m",Superscript [Str "4"],Str "\8211\&20\160m",Superscript [Str "4"]]]
[ Para
[ Str "10\160m"
, Superscript
[ Str "4" ]
, Str "\8211\&20\160m"
, Superscript
[ Str "4" ]
]
]
```
@ -136,12 +206,12 @@
% pandoc -f latex -t native
\SIrange[round-precision=2]{10}{20}{\gram}
^D
[Para [Str "10\160g\8211\&20\160g"]]
[ Para [ Str "10\160g\8211\&20\160g" ] ]
```
```
% pandoc -f latex -t native
\SIrange[round-precision=2]{10.0}{20.25}{\gram}
^D
[Para [Str "10.0\160g\8211\&20.25\160g"]]
[ Para [ Str "10.0\160g\8211\&20.25\160g" ] ]
```

View file

@ -4,7 +4,34 @@
Software developers create \cicd pipelines to… Following issue can be resolved by \cicd:
^D
[Para [Str "Software",Space,Str "developers",Space,Str "create",Space,Str "CI/CD",Space,Str "pipelines",Space,Str "to\8230",Space,Str "Following",Space,Str "issue",Space,Str "can",Space,Str "be",Space,Str "resolved",Space,Str "by",Space,Str "CI/CD:"]]
[ Para
[ Str "Software"
, Space
, Str "developers"
, Space
, Str "create"
, Space
, Str "CI/CD"
, Space
, Str "pipelines"
, Space
, Str "to\8230"
, Space
, Str "Following"
, Space
, Str "issue"
, Space
, Str "can"
, Space
, Str "be"
, Space
, Str "resolved"
, Space
, Str "by"
, Space
, Str "CI/CD:"
]
]
```
```
@ -13,7 +40,22 @@ Software developers create \cicd pipelines to… Following issue can be resolved
\cicd\footnote{\url{https://en.wikipedia.org/wiki/CI/CD}} is awesome.
^D
[Para [Str "CI/CD",Note [Para [Link ("",[],[]) [Str "https://en.wikipedia.org/wiki/CI/CD"] ("https://en.wikipedia.org/wiki/CI/CD","")]],Space,Str "is",Space,Str "awesome."]]
[ Para
[ Str "CI/CD"
, Note
[ Para
[ Link
( "", [], [] )
[ Str "https://en.wikipedia.org/wiki/CI/CD" ]
( "https://en.wikipedia.org/wiki/CI/CD", "" )
]
]
, Space
, Str "is"
, Space
, Str "awesome."
]
]
```
```
@ -23,5 +65,5 @@ Software developers create \cicd pipelines to… Following issue can be resolved
\cicd\pipeline.
^D
[Para [Str "CI/CD",Space,Str "pipeline."]]
[ Para [ Str "CI/CD", Space, Str "pipeline." ] ]
```

View file

@ -15,36 +15,80 @@ Results marker can be hidden in block attributes (#3706)
| 2 | La |
| 3 | La |
^D
[Div ("tab",[],[])
[Table ("",[],[]) (Caption Nothing
[Plain [Str "Lalelu."]])
[(AlignDefault,ColWidthDefault)
,(AlignDefault,ColWidthDefault)]
(TableHead ("",[],[])
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Id"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Desc"]]]])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "1"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "La"]]]
,Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "2"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "La"]]]
,Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "3"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "La"]]]])]
(TableFoot ("",[],[])
[])]]
[ Div
( "tab", [], [] )
[ Table
( "", [], [] )
( Caption Nothing [ Plain [ Str "Lalelu." ] ] )
[
( AlignDefault, ColWidthDefault )
,
( AlignDefault, ColWidthDefault )
]
( TableHead
( "", [], [] )
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Id" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Desc" ] ]
]
]
)
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "1" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "La" ] ]
]
, Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "2" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "La" ] ]
]
, Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "3" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "La" ] ]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
]
```
```

View file

@ -5,24 +5,42 @@
C & D
\end{tabular}
^D
[Table ("",[],[]) (Caption Nothing
[])
[(AlignCenter,ColWidthDefault)
,(AlignCenter,ColWidthDefault)]
(TableHead ("",[],[])
[])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "A"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "B&1"]]]
,Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "C"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "D"]]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [] )
[ ( AlignCenter, ColWidthDefault ), ( AlignCenter, ColWidthDefault ) ]
( TableHead ( "", [], [] ) [] )
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "A" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "B&1" ] ]
]
, Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "C" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "D" ] ]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```

View file

@ -6,8 +6,9 @@
some: code
```
^D
[BulletList
[[Plain [Str "Item1"]]
,[Plain [Str "Item2"]]]
,CodeBlock ("",["yaml"],[]) "some: code"]
[ BulletList
[ [ Plain [ Str "Item1" ] ], [ Plain [ Str "Item2" ] ] ]
, CodeBlock
( "", [ "yaml" ], [] ) "some: code"
]
````

View file

@ -5,8 +5,19 @@ title: 'Titel'
date: '22. Juni 2017'
---
^D
Pandoc (Meta {unMeta = fromList [("date",MetaInlines [Str "22.",Space,Str "Juni",Space,Str "2017"]),("title",MetaInlines [Str "Titel"])]})
[]
Pandoc
( Meta
{ unMeta = fromList
[
( "date"
, MetaInlines
[ Str "22.", Space, Str "Juni", Space, Str "2017" ]
)
,
( "title", MetaInlines [ Str "Titel" ] )
]
}
) []
```
```
@ -17,7 +28,24 @@ date: |
22. Juni 2017
---
^D
Pandoc (Meta {unMeta = fromList [("date",MetaBlocks [OrderedList (22,Decimal,Period) [[Plain [Str "Juni",Space,Str "2017"]]]]),("title",MetaBlocks [Div ("",[],[]) [Plain [Str "foo"]]])]})
[]
Pandoc
( Meta
{ unMeta = fromList
[
( "date"
, MetaBlocks
[ OrderedList
( 22, Decimal, Period )
[ [ Plain [ Str "Juni", Space, Str "2017" ] ] ]
]
)
,
( "title"
, MetaBlocks
[ Div ( "", [], [] ) [ Plain [ Str "foo" ] ] ]
)
]
}
) []
```

View file

@ -20,9 +20,40 @@
Pandoc is 300\% awesome.
}
^D
[BulletList
[[Para [Str "Pandoc",Space,Str "is",Space,Str "100%",Space,Str "awesome."]]]
,BulletList
[[Para [Str "Pandoc",Space,Str "is",Space,Str "200%",Space,Str "awesome."]]]
,Para [Str "Pandoc",Space,Str "is",Space,Str "300%",Space,Str "awesome."]]
[ BulletList
[
[ Para
[ Str "Pandoc"
, Space
, Str "is"
, Space
, Str "100%"
, Space
, Str "awesome."
]
]
]
, BulletList
[
[ Para
[ Str "Pandoc"
, Space
, Str "is"
, Space
, Str "200%"
, Space
, Str "awesome."
]
]
]
, Para
[ Str "Pandoc"
, Space
, Str "is"
, Space
, Str "300%"
, Space
, Str "awesome."
]
]
```

View file

@ -2,6 +2,5 @@
% pandoc -f html -t native
<div><p>hello</div>
^D
[Div ("",[],[])
[Para [Str "hello"]]]
[ Div ( "", [], [] ) [ Para [ Str "hello" ] ] ]
```

View file

@ -2,5 +2,7 @@
% pandoc -t native
\titleformat{\chapter}[display]{\normalfont\large\bfseries}{第\thechapter{}章}{20pt}{\Huge}
^D
[RawBlock (Format "tex") "\\titleformat{\\chapter}[display]{\\normalfont\\large\\bfseries}{\31532\\thechapter{}\31456}{20pt}{\\Huge}"]
[ RawBlock
( Format "tex" ) "\\titleformat{\\chapter}[display]{\\normalfont\\large\\bfseries}{\31532\\thechapter{}\31456}{20pt}{\\Huge}"
]
```

View file

@ -20,7 +20,11 @@ more
hello \iftoggle{ebook}{ebook}{noebook}
^D
[Para [Str "ebook",SoftBreak,Str "more"]
,Para [Str "not",Space,Str "ebook",SoftBreak,Str "more"]
,Para [Str "hello",Space,Str "noebook"]]
[ Para
[ Str "ebook", SoftBreak, Str "more" ]
, Para
[ Str "not", Space, Str "ebook", SoftBreak, Str "more" ]
, Para
[ Str "hello", Space, Str "noebook" ]
]
```

View file

@ -2,5 +2,5 @@
% pandoc -f rst -t native
.. include:: command/3880.txt
^D
[Para [Str "hi"]]
[ Para [ Str "hi" ] ]
```

View file

@ -4,8 +4,16 @@
<pre>blabla</pre>
# more
^D
[OrderedList (1,DefaultStyle,DefaultDelim)
[[Plain [Str "text",Space,Str "text"]
,CodeBlock ("",[],[]) "blabla"]
,[Plain [Str "more"]]]]
[ OrderedList
( 1, DefaultStyle, DefaultDelim )
[
[ Plain
[ Str "text", Space, Str "text" ]
, CodeBlock
( "", [], [] ) "blabla"
]
,
[ Plain [ Str "more" ] ]
]
]
```

View file

@ -6,6 +6,9 @@
Another Code block
^D
[RawBlock (Format "tex") "\\newpage"
,CodeBlock ("",[],[]) "Code block\n\nAnother Code block"]
[ RawBlock
( Format "tex" ) "\\newpage"
, CodeBlock
( "", [], [] ) "Code block\n\nAnother Code block"
]
```

View file

@ -2,19 +2,19 @@
% pandoc -f latex -t native
\texttt{"hi"}
^D
[Para [Code ("",[],[]) "\"hi\""]]
[ Para [ Code ( "", [], [] ) "\"hi\"" ] ]
```
```
% pandoc -f latex -t native
\texttt{``hi''}
^D
[Para [Code ("",[],[]) "\8220hi\8221"]]
[ Para [ Code ( "", [], [] ) "\8220hi\8221" ] ]
```
```
% pandoc -f latex -t native
\texttt{`hi'}
^D
[Para [Code ("",[],[]) "\8216hi\8217"]]
[ Para [ Code ( "", [], [] ) "\8216hi\8217" ] ]
```

View file

@ -5,5 +5,5 @@
\code{f}
\end{document}
^D
[Para [Code ("",[],[]) "f"]]
[ Para [ Code ( "", [], [] ) "f" ] ]
```

View file

@ -5,8 +5,11 @@
\graphicspath\expandafter{\expandafter{\filename@area}}%
\makeatother
^D
[RawBlock (Format "latex") "\\makeatletter"
,RawBlock (Format "latex") "\\makeatother"]
[ RawBlock
( Format "latex" ) "\\makeatletter"
, RawBlock
( Format "latex" ) "\\makeatother"
]
```
```
@ -16,8 +19,11 @@
\DeclareRobustCommand{\urlfootnote}{\hyper@normalise\urlfootnote@}
\makeatother
^D
[RawBlock (Format "latex") "\\makeatletter"
,RawBlock (Format "latex") "\\makeatother"]
[ RawBlock
( Format "latex" ) "\\makeatletter"
, RawBlock
( Format "latex" ) "\\makeatother"
]
```
```
@ -25,5 +31,5 @@
\def\foo{bar}
\expandafter\bam\foo
^D
[RawBlock (Format "latex") "\\bambar"]
[ RawBlock ( Format "latex" ) "\\bambar" ]
```

View file

@ -3,5 +3,22 @@
<span title="1st line of text <br> 2nd line of text">foo</span>
<span title="1st line of text <br> 2nd line of text">foo</span>
^D
[Para [Span ("",[],[("title","1st line of text <br> 2nd line of text")]) [Str "foo"],SoftBreak,Span ("",[],[("title","1st line of text <br> 2nd line of text")]) [Str "foo"]]]
[ Para
[ Span
( ""
, []
,
[ ( "title", "1st line of text <br> 2nd line of text" ) ]
)
[ Str "foo" ]
, SoftBreak
, Span
( ""
, []
,
[ ( "title", "1st line of text <br> 2nd line of text" ) ]
)
[ Str "foo" ]
]
]
```

View file

@ -3,7 +3,7 @@
\newcommand\arrow\to
$a\arrow b$
^D
[Para [Math InlineMath "a\\to b"]]
[ Para [ Math InlineMath "a\\to b" ] ]
```
```
@ -11,7 +11,7 @@ $a\arrow b$
\newcommand\pfeil[1]{\to #1}
$a\pfeil b$
^D
[Para [Math InlineMath "a\\to b"]]
[ Para [ Math InlineMath "a\\to b" ] ]
```
```
@ -19,5 +19,5 @@ $a\pfeil b$
\newcommand\fleche{\to}
$a\fleche b$
^D
[Para [Math InlineMath "a\\to b"]]
[ Para [ Math InlineMath "a\\to b" ] ]
```

View file

@ -2,13 +2,17 @@
% pandoc -t native -s -M title=New
% Old
^D
Pandoc (Meta {unMeta = fromList [("title",MetaString "New")]})
[]
Pandoc
( Meta { unMeta = fromList [ ( "title", MetaString "New" ) ] } ) []
```
```
% pandoc -t native -s -M foo=1 -M foo=2
^D
Pandoc (Meta {unMeta = fromList [("foo",MetaList [MetaString "1",MetaString "2"])]})
[]
Pandoc
( Meta
{ unMeta = fromList
[ ( "foo", MetaList [ MetaString "1", MetaString "2" ] ) ]
}
) []
```

View file

@ -5,7 +5,9 @@
\end{shaded}
}
^D
[RawBlock (Format "tex") "\\parbox[t]{0.4\\textwidth}{\n\\begin{shaded}\n\\end{shaded}\n}"]
[ RawBlock
( Format "tex" ) "\\parbox[t]{0.4\\textwidth}{\n\\begin{shaded}\n\\end{shaded}\n}"
]
```
```
@ -14,22 +16,40 @@
Blah & Foo & Bar \\
\end{tabular}
^D
[Table ("",[],[]) (Caption Nothing
[])
[(AlignLeft,ColWidthDefault)
,(AlignRight,ColWidthDefault)
,(AlignRight,ColWidthDefault)]
(TableHead ("",[],[])
[])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Blah"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Foo"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Bar"]]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [] )
[
( AlignLeft, ColWidthDefault )
,
( AlignRight, ColWidthDefault )
,
( AlignRight, ColWidthDefault )
]
( TableHead ( "", [], [] ) [] )
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Blah" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Foo" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Bar" ] ]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```

View file

@ -11,19 +11,29 @@
</tr>
</table>
^D
[Table ("",[],[]) (Caption Nothing
[])
[(AlignDefault,ColWidth 0.3)
,(AlignDefault,ColWidth 0.7)]
(TableHead ("",[],[])
[])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "1"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "2"]]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [] )
[ ( AlignDefault, ColWidth 0.3 ), ( AlignDefault, ColWidth 0.7 ) ]
( TableHead ( "", [], [] ) [] )
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "1" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "2" ] ]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```

View file

@ -4,6 +4,25 @@
[http://domain.com?a=. open productname bugs]
^D
[Para [Link ("",[],[]) [Str "open",Space,Str "productname",Space,Str "bugs"] ("https://domain.com/script.php?a=1&b=2&c=&d=4","")]
,Para [Str "[",Link ("",[],[]) [Str "http://domain.com?a="] ("http://domain.com?a=",""),Str ".",Space,Str "open",Space,Str "productname",Space,Str "bugs]"]]
[ Para
[ Link
( "", [], [] )
[ Str "open", Space, Str "productname", Space, Str "bugs" ]
( "https://domain.com/script.php?a=1&b=2&c=&d=4", "" )
]
, Para
[ Str "["
, Link
( "", [], [] )
[ Str "http://domain.com?a=" ]
( "http://domain.com?a=", "" )
, Str "."
, Space
, Str "open"
, Space
, Str "productname"
, Space
, Str "bugs]"
]
]
```

View file

@ -8,25 +8,52 @@
not a caption!
::::::::::::::::
^D
[Table ("",[],[]) (Caption Nothing
[])
[(AlignDefault,ColWidthDefault)
,(AlignDefault,ColWidthDefault)]
(TableHead ("",[],[])
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "col1"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "col2"]]]])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "1"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "2"]]]])]
(TableFoot ("",[],[])
[])
,Div ("",["notes"],[])
[Para [Str "not",Space,Str "a",Space,Str "caption!"]]]
[ Table
( "", [], [] )
( Caption Nothing [] )
[
( AlignDefault, ColWidthDefault )
,
( AlignDefault, ColWidthDefault )
]
( TableHead
( "", [], [] )
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "col1" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "col2" ] ]
]
]
)
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "1" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "2" ] ]
]
]
]
( TableFoot ( "", [], [] ) [] )
, Div
( "", [ "notes" ], [] )
[ Para [ Str "not", Space, Str "a", Space, Str "caption!" ] ]
]
```

View file

@ -3,7 +3,7 @@
Hello.\
world.
^D
[Para [Str "Hello.\160world."]]
[ Para [ Str "Hello.\160world." ] ]
```
```
@ -11,7 +11,7 @@ world.
Hello.\
world.
^D
[Para [Str "Hello.\160world."]]
[ Para [ Str "Hello.\160world." ] ]
```
```
@ -20,6 +20,5 @@ Hello.\
World.
^D
[Para [Str "Hello.\160"]
,Para [Str "World."]]
[ Para [ Str "Hello.\160" ], Para [ Str "World." ] ]
```

View file

@ -3,6 +3,9 @@
\newcommand{\gen}{a\ Gen\ b}
abc
^D
[RawBlock (Format "tex") "\\newcommand{\\gen}{a\\ Gen\\ b}"
,Para [Str "abc"]]
[ RawBlock
( Format "tex" ) "\\newcommand{\\gen}{a\\ Gen\\ b}"
, Para
[ Str "abc" ]
]
```

View file

@ -3,8 +3,5 @@
<div class="line-block">hi<br /><br>
 there</div>
^D
[LineBlock
[[Str "hi"]
,[]
,[Str "\160there"]]]
[ LineBlock [ [ Str "hi" ], [], [ Str "\160there" ] ] ]
```

View file

@ -4,7 +4,7 @@
<img src="foo" alt="bar">
</figure>
^D
[Para [Image ("",[],[]) [] ("foo","fig:")]]
[ Para [ Image ( "", [], [] ) [] ( "foo", "fig:" ) ] ]
```
```
@ -18,7 +18,7 @@
</figcaption>
</figure>
^D
[Para [Image ("",[],[]) [Str "baz"] ("foo","fig:")]]
[ Para [ Image ( "", [], [] ) [ Str "baz" ] ( "foo", "fig:" ) ] ]
```
```
@ -28,5 +28,7 @@
<figcaption><p><em>baz</em></p></figcaption>
</figure>
^D
[Para [Image ("",[],[]) [Emph [Str "baz"]] ("foo","fig:")]]
[ Para
[ Image ( "", [], [] ) [ Emph [ Str "baz" ] ] ( "foo", "fig:" ) ]
]
```

View file

@ -4,7 +4,12 @@
This should retain the four leading spaces
#+end_example
^D
[CodeBlock ("",["example"],[]) " This should retain the four leading spaces\n"]
[ CodeBlock
( ""
, [ "example" ]
, []
) " This should retain the four leading spaces\n"
]
```
```

View file

@ -4,7 +4,5 @@
a
- b
^D
[BulletList
[[Plain [Str "a"]]
,[Plain [Str "b"]]]]
[ BulletList [ [ Plain [ Str "a" ] ], [ Plain [ Str "b" ] ] ] ]
```

View file

@ -2,5 +2,5 @@
% pandoc -f latex -t native
\foreignlanguage{ngerman}{foo}
^D
[Para [Span ("",[],[("lang","de-DE")]) [Str "foo"]]]
[ Para [ Span ( "", [], [ ( "lang", "de-DE" ) ] ) [ Str "foo" ] ] ]
```

View file

@ -25,9 +25,27 @@ header3
header4
~~~~~~~
^D
Pandoc (Meta {unMeta = fromList [("subtitle",MetaInlines [Str "Subtitle"]),("title",MetaInlines [Str "Title"])]})
[Header 1 ("header1",[],[]) [Str "header1"]
,Header 2 ("header2",[],[]) [Str "header2"]
,Header 3 ("id",[],[]) [Str "header3"]
,Header 3 ("id3",[],[]) [Str "header4",Span ("id2",[],[]) []]]
Pandoc
( Meta
{ unMeta = fromList
[
( "subtitle", MetaInlines [ Str "Subtitle" ] )
,
( "title", MetaInlines [ Str "Title" ] )
]
}
)
[ Header 1
( "header1", [], [] )
[ Str "header1" ]
, Header 2
( "header2", [], [] )
[ Str "header2" ]
, Header 3
( "id", [], [] )
[ Str "header3" ]
, Header 3
( "id3", [], [] )
[ Str "header4", Span ( "id2", [], [] ) [] ]
]
```

View file

@ -4,5 +4,5 @@
\noop{\newcommand{\foo}[1]{#1}}
\foo{hi}
^D
[Para [Str "hi"]]
[ Para [ Str "hi" ] ]
```

View file

@ -3,5 +3,5 @@
Driver
------
^D
[Header 1 ("driver",[],[]) [Str "Driver"]]
[ Header 1 ( "driver", [], [] ) [ Str "Driver" ] ]
```

View file

@ -9,10 +9,18 @@
:::
::::
^D
[Div ("",["a"],[])
[BulletList
[[Div ("",["b"],[])
[Para [Str "text"]]
,Div ("",["c"],[])
[Para [Str "text"]]]]]]
[ Div
( "", [ "a" ], [] )
[ BulletList
[
[ Div
( "", [ "b" ], [] )
[ Para [ Str "text" ] ]
, Div
( "", [ "c" ], [] )
[ Para [ Str "text" ] ]
]
]
]
]
```

View file

@ -8,7 +8,31 @@
** Children of headers with excluded tags should not appear :xylophone:
* This should not appear :%:
^D
[Header 1 ("noexport-should-appear-if-not-specified-in-excludetags",[],[]) [Str "NOEXPORT",Space,Str "should",Space,Str "appear",Space,Str "if",Space,Str "not",Space,Str "specified",Space,Str "in",Space,Str "EXCLUDE",Subscript [Str "TAGS"],Space,Span ("",["tag"],[("tag-name","noexport")]) [SmallCaps [Str "noexport"]]]]
[ Header 1
( "noexport-should-appear-if-not-specified-in-excludetags", [], [] )
[ Str "NOEXPORT"
, Space
, Str "should"
, Space
, Str "appear"
, Space
, Str "if"
, Space
, Str "not"
, Space
, Str "specified"
, Space
, Str "in"
, Space
, Str "EXCLUDE"
, Subscript
[ Str "TAGS" ]
, Space
, Span
( "", [ "tag" ], [ ( "tag-name", "noexport" ) ] )
[ SmallCaps [ Str "noexport" ] ]
]
]
```
```
@ -17,7 +41,19 @@
* This should not appear :elephant:
* This should appear :fawn:
^D
[Header 1 ("this-should-appear",[],[]) [Str "This",Space,Str "should",Space,Str "appear",Space,Span ("",["tag"],[("tag-name","fawn")]) [SmallCaps [Str "fawn"]]]]
[ Header 1
( "this-should-appear", [], [] )
[ Str "This"
, Space
, Str "should"
, Space
, Str "appear"
, Space
, Span
( "", [ "tag" ], [ ( "tag-name", "fawn" ) ] )
[ SmallCaps [ Str "fawn" ] ]
]
]
```
```
@ -28,7 +64,19 @@
* This should not appear :hippo:
* This should appear :noexport:
^D
[Header 1 ("this-should-appear",[],[]) [Str "This",Space,Str "should",Space,Str "appear",Space,Span ("",["tag"],[("tag-name","noexport")]) [SmallCaps [Str "noexport"]]]]
[ Header 1
( "this-should-appear", [], [] )
[ Str "This"
, Space
, Str "should"
, Space
, Str "appear"
, Space
, Span
( "", [ "tag" ], [ ( "tag-name", "noexport" ) ] )
[ SmallCaps [ Str "noexport" ] ]
]
]
```
```
@ -36,5 +84,29 @@
#+EXCLUDE_TAGS:
* NOEXPORT should appear if not specified in EXCLUDE_TAGS :noexport:
^D
[Header 1 ("noexport-should-appear-if-not-specified-in-excludetags",[],[]) [Str "NOEXPORT",Space,Str "should",Space,Str "appear",Space,Str "if",Space,Str "not",Space,Str "specified",Space,Str "in",Space,Str "EXCLUDE",Subscript [Str "TAGS"],Space,Span ("",["tag"],[("tag-name","noexport")]) [SmallCaps [Str "noexport"]]]]
[ Header 1
( "noexport-should-appear-if-not-specified-in-excludetags", [], [] )
[ Str "NOEXPORT"
, Space
, Str "should"
, Space
, Str "appear"
, Space
, Str "if"
, Space
, Str "not"
, Space
, Str "specified"
, Space
, Str "in"
, Space
, Str "EXCLUDE"
, Subscript
[ Str "TAGS" ]
, Space
, Span
( "", [ "tag" ], [ ( "tag-name", "noexport" ) ] )
[ SmallCaps [ Str "noexport" ] ]
]
]
```

View file

@ -6,5 +6,18 @@
The file id is \nolinkurl{ESP_123_5235}.
\end{document}
^D
[Para [Str "The",Space,Str "file",Space,Str "id",Space,Str "is",Space,Code ("",[],[]) "ESP_123_5235",Str "."]]
[ Para
[ Str "The"
, Space
, Str "file"
, Space
, Str "id"
, Space
, Str "is"
, Space
, Code
( "", [], [] ) "ESP_123_5235"
, Str "."
]
]
```

View file

@ -3,5 +3,18 @@
\cite{a%
}
^D
[Para [Cite [Citation {citationId = "a", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cite{a%\n}"]]]
[ Para
[ Cite
[ Citation
{ citationId = "a"
, citationPrefix = []
, citationSuffix = []
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
]
[ RawInline ( Format "latex" ) "\\cite{a%\n}" ]
]
]
```

View file

@ -4,7 +4,5 @@
=====
^D
[BulletList
[[]]
,HorizontalRule]
[ BulletList [ [] ], HorizontalRule ]
```

View file

@ -6,5 +6,5 @@
Test
\end{document}
^D
[Para [Str "Test"]]
[ Para [ Str "Test" ] ]
```

View file

@ -3,7 +3,5 @@
• a
• b
^D
[BulletList
[[Plain [Str "a"]]
,[Plain [Str "b"]]]]
[ BulletList [ [ Plain [ Str "a" ] ], [ Plain [ Str "b" ] ] ] ]
```

View file

@ -9,7 +9,7 @@
% pandoc -f latex+raw_tex -t native
\mbox{abc def}
^D
[Para [RawInline (Format "latex") "\\mbox{abc def}"]]
[ Para [ RawInline ( Format "latex" ) "\\mbox{abc def}" ] ]
```
```
@ -53,7 +53,7 @@ mno} pqr
% pandoc -f latex+raw_tex -t native
\hbox{abc def}
^D
[Para [RawInline (Format "latex") "\\hbox{abc def}"]]
[ Para [ RawInline ( Format "latex" ) "\\hbox{abc def}" ] ]
```
```

View file

@ -2,19 +2,32 @@
% pandoc -f textile -t native
|_. heading 1 |_. heading 2|
^D
[Table ("",[],[]) (Caption Nothing
[])
[(AlignDefault,ColWidthDefault)
,(AlignDefault,ColWidthDefault)]
(TableHead ("",[],[])
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "heading",Space,Str "1"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "heading",Space,Str "2"]]]])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [] )
[
( AlignDefault, ColWidthDefault )
,
( AlignDefault, ColWidthDefault )
]
( TableHead
( "", [], [] )
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "heading", Space, Str "1" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "heading", Space, Str "2" ] ]
]
]
)
[ TableBody ( "", [], [] ) ( RowHeadColumns 0 ) [] [] ]
( TableFoot ( "", [], [] ) [] )
]
```

View file

@ -30,6 +30,7 @@ This has <span class="smallcaps">small caps</span> in it.
This has <s>strikeout</s> in it.
^D
This has strikeout in it.
```
```
% pandoc --wrap=none -f html -t commonmark+raw_html-strikeout

View file

@ -2,14 +2,13 @@
% pandoc -f latex -t native
foo \include{command/bar}
^D
[Para [Str "foo"]
,Para [Emph [Str "hi",Space,Str "there"]]]
[ Para [ Str "foo" ], Para [ Emph [ Str "hi", Space, Str "there" ] ] ]
```
```
% pandoc -f latex -t native
foo \input{command/bar}
^D
[Para [Str "foo",Space,Emph [Str "hi",Space,Str "there"]]]
[ Para [ Str "foo", Space, Emph [ Str "hi", Space, Str "there" ] ] ]
```

View file

@ -2,5 +2,5 @@
% pandoc -f latex -t native
$\rho_\text{D$_2$O}=866$
^D
[Para [Math InlineMath "\\rho_\\text{D$_2$O}=866"]]
[ Para [ Math InlineMath "\\rho_\\text{D$_2$O}=866" ] ]
```

View file

@ -8,23 +8,49 @@
* - spam
- ham
^D
[Table ("",[],[]) (Caption Nothing
[])
[(AlignDefault,ColWidthDefault)
,(AlignDefault,ColWidthDefault)]
(TableHead ("",[],[])
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Foo"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Bar"]]]])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "spam"]]
,Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "ham"]]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [] )
[
( AlignDefault, ColWidthDefault )
,
( AlignDefault, ColWidthDefault )
]
( TableHead
( "", [], [] )
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Foo" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Bar" ] ]
]
]
)
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "spam" ] ]
, Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "ham" ] ]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```

View file

@ -22,9 +22,15 @@ code4
\begin{verbatim}
code5\end{verbatim}
^D
[CodeBlock ("",[],[("key1","value1")]) "code1\n"
,CodeBlock ("",[],[("key2","value2")]) "code2\n "
,CodeBlock ("",[],[]) "code3"
,CodeBlock ("",[],[]) "code4"
,CodeBlock ("",[],[]) "code5"]
[ CodeBlock
( "", [], [ ( "key1", "value1" ) ] ) "code1\n"
, CodeBlock
( "", [], [ ( "key2", "value2" ) ] ) "code2\n "
, CodeBlock
( "", [], [] ) "code3"
, CodeBlock
( "", [], [] ) "code4"
, CodeBlock
( "", [], [] ) "code5"
]
```

View file

@ -3,7 +3,7 @@
(cf.
foo)
^D
[Para [Str "(cf.",SoftBreak,Str "foo)"]]
[ Para [ Str "(cf.", SoftBreak, Str "foo)" ] ]
```
```
@ -11,7 +11,7 @@ foo)
a (cf.
foo)
^D
[Para [Str "a",Space,Str "(cf.",SoftBreak,Str "foo)"]]
[ Para [ Str "a", Space, Str "(cf.", SoftBreak, Str "foo)" ] ]
```
```
@ -19,7 +19,7 @@ foo)
cf.
foo
^D
[Para [Str "cf.",SoftBreak,Str "foo"]]
[ Para [ Str "cf.", SoftBreak, Str "foo" ] ]
```
```
@ -27,5 +27,5 @@ foo
a cf.
foo
^D
[Para [Str "a",Space,Str "cf.",SoftBreak,Str "foo"]]
[ Para [ Str "a", Space, Str "cf.", SoftBreak, Str "foo" ] ]
```

View file

@ -6,8 +6,11 @@
while (n > 0) {
\end{verbatim}
^D
[Para [Span ("",[],[]) [Code ("",[],[]) "<-"]]
,CodeBlock ("",[],[]) " while (n > 0) {"]
[ Para
[ Span ( "", [], [] ) [ Code ( "", [], [] ) "<-" ] ]
, CodeBlock
( "", [], [] ) " while (n > 0) {"
]
```
```
@ -20,10 +23,17 @@
\item<beamer:2> five
\end{itemize}
^D
[BulletList
[[Para [Str "one"]]
,[Para [Str "two"]]
,[Para [Str "three"]]
,[Para [Str "four"]]
,[Para [Str "five"]]]]
[ BulletList
[
[ Para [ Str "one" ] ]
,
[ Para [ Str "two" ] ]
,
[ Para [ Str "three" ] ]
,
[ Para [ Str "four" ] ]
,
[ Para [ Str "five" ] ]
]
]
```

View file

@ -11,6 +11,26 @@
acquisizione-software.rst
riuso-software.rst
^D
[Div ("tree1",["toctree","foo","bar"],[("caption","Indice dei contenuti"),("numbered",""),("maxdepth","3")])
[Para [Str "premessa.rst",SoftBreak,Str "acquisizione-software.rst",SoftBreak,Str "riuso-software.rst"]]]
[ Div
( "tree1"
,
[ "toctree", "foo", "bar" ]
,
[
( "caption", "Indice dei contenuti" )
,
( "numbered", "" )
,
( "maxdepth", "3" )
]
)
[ Para
[ Str "premessa.rst"
, SoftBreak
, Str "acquisizione-software.rst"
, SoftBreak
, Str "riuso-software.rst"
]
]
]
```

View file

@ -6,14 +6,25 @@
***Level 3
*Level 1
^D
[BulletList
[[Plain [Str "Level",Space,Str "1"]]
,[Plain [Str "Level",Space,Str "1"]
,BulletList
[[Plain [Str "Level",Space,Str "2"]
,BulletList
[[Plain [Str "Level",Space,Str "3"]]]]]]
,[Plain [Str "Level",Space,Str "1"]]]]
[ BulletList
[
[ Plain [ Str "Level", Space, Str "1" ] ]
,
[ Plain
[ Str "Level", Space, Str "1" ]
, BulletList
[
[ Plain
[ Str "Level", Space, Str "2" ]
, BulletList
[ [ Plain [ Str "Level", Space, Str "3" ] ] ]
]
]
]
,
[ Plain [ Str "Level", Space, Str "1" ] ]
]
]
```
```
% pandoc -f tikiwiki -t native
@ -23,12 +34,26 @@
###Level 3
#Level 1
^D
[OrderedList (1,DefaultStyle,DefaultDelim)
[[Plain [Str "Level",Space,Str "1"]]
,[Plain [Str "Level",Space,Str "1"]
,OrderedList (1,DefaultStyle,DefaultDelim)
[[Plain [Str "Level",Space,Str "2"]
,OrderedList (1,DefaultStyle,DefaultDelim)
[[Plain [Str "Level",Space,Str "3"]]]]]]
,[Plain [Str "Level",Space,Str "1"]]]]
[ OrderedList
( 1, DefaultStyle, DefaultDelim )
[
[ Plain [ Str "Level", Space, Str "1" ] ]
,
[ Plain
[ Str "Level", Space, Str "1" ]
, OrderedList
( 1, DefaultStyle, DefaultDelim )
[
[ Plain
[ Str "Level", Space, Str "2" ]
, OrderedList
( 1, DefaultStyle, DefaultDelim )
[ [ Plain [ Str "Level", Space, Str "3" ] ] ]
]
]
]
,
[ Plain [ Str "Level", Space, Str "1" ] ]
]
]
```

View file

@ -5,7 +5,17 @@ extension properly.
% pandoc -f commonmark+gfm_auto_identifiers+ascii_identifiers -t native
# non ascii ⚠️ räksmörgås
^D
[Header 1 ("non-ascii--raksmorgas",[],[]) [Str "non",Space,Str "ascii",Space,Str "\9888\65039",Space,Str "r\228ksm\246rg\229s"]]
[ Header 1
( "non-ascii--raksmorgas", [], [] )
[ Str "non"
, Space
, Str "ascii"
, Space
, Str "\9888\65039"
, Space
, Str "r\228ksm\246rg\229s"
]
]
```
Note that the emoji here is actually a composite character,
@ -16,7 +26,17 @@ so it survives...
% pandoc -f commonmark+gfm_auto_identifiers-ascii_identifiers -t native
# non ascii ⚠️ räksmörgås
^D
[Header 1 ("non-ascii-\65039-r\228ksm\246rg\229s",[],[]) [Str "non",Space,Str "ascii",Space,Str "\9888\65039",Space,Str "r\228ksm\246rg\229s"]]
[ Header 1
( "non-ascii-\65039-r\228ksm\246rg\229s", [], [] )
[ Str "non"
, Space
, Str "ascii"
, Space
, Str "\9888\65039"
, Space
, Str "r\228ksm\246rg\229s"
]
]
```
`gfm` should have `ascii_identifiers` disabled by default.
@ -25,5 +45,15 @@ so it survives...
% pandoc -f gfm -t native
# non ascii ⚠️ räksmörgås
^D
[Header 1 ("non-ascii-\65039-r\228ksm\246rg\229s",[],[]) [Str "non",Space,Str "ascii",Space,Str "\9888\65039",Space,Str "r\228ksm\246rg\229s"]]
[ Header 1
( "non-ascii-\65039-r\228ksm\246rg\229s", [], [] )
[ Str "non"
, Space
, Str "ascii"
, Space
, Str "\9888\65039"
, Space
, Str "r\228ksm\246rg\229s"
]
]
```

View file

@ -4,14 +4,34 @@ Test that emojis are wrapped in Span
% pandoc -f commonmark+emoji -t native
My:thumbsup:emoji:heart:
^D
[Para [Str "My",Span ("",["emoji"],[("data-emoji","thumbsup")]) [Str "\128077"],Str "emoji",Span ("",["emoji"],[("data-emoji","heart")]) [Str "\10084\65039"]]]
[ Para
[ Str "My"
, Span
( "", [ "emoji" ], [ ( "data-emoji", "thumbsup" ) ] )
[ Str "\128077" ]
, Str "emoji"
, Span
( "", [ "emoji" ], [ ( "data-emoji", "heart" ) ] )
[ Str "\10084\65039" ]
]
]
```
```
% pandoc -f markdown+emoji -t native
My:thumbsup:emoji:heart:
^D
[Para [Str "My",Span ("",["emoji"],[("data-emoji","thumbsup")]) [Str "\128077"],Str "emoji",Span ("",["emoji"],[("data-emoji","heart")]) [Str "\10084\65039"]]]
[ Para
[ Str "My"
, Span
( "", [ "emoji" ], [ ( "data-emoji", "thumbsup" ) ] )
[ Str "\128077" ]
, Str "emoji"
, Span
( "", [ "emoji" ], [ ( "data-emoji", "heart" ) ] )
[ Str "\10084\65039" ]
]
]
```
```

View file

@ -6,9 +6,13 @@ Markdown parsed *here*
*But not here*
^D
[Para [Str "Markdown",Space,Str "parsed",Space,Emph [Str "here"]]
,RawBlock (Format "tex") "\\include{command/bar}"
,Para [Emph [Str "But",Space,Str "not",Space,Str "here"]]]
[ Para
[ Str "Markdown", Space, Str "parsed", Space, Emph [ Str "here" ] ]
, RawBlock
( Format "tex" ) "\\include{command/bar}"
, Para
[ Emph [ Str "But", Space, Str "not", Space, Str "here" ] ]
]
```
```
@ -17,6 +21,14 @@ Markdown parsed *here*
*But not here*
^D
[Para [Emph [Str "here"],Space,RawInline (Format "tex") "\\input{command/bar}"]
,Para [Emph [Str "But",Space,Str "not",Space,Str "here"]]]
[ Para
[ Emph
[ Str "here" ]
, Space
, RawInline
( Format "tex" ) "\\input{command/bar}"
]
, Para
[ Emph [ Str "But", Space, Str "not", Space, Str "here" ] ]
]
```

View file

@ -6,8 +6,7 @@ No blank lines in inline interpreted roles:
blank`:myrole:
^D
[Para [Str "`no"]
,Para [Str "blank`:myrole:"]]
[ Para [ Str "`no" ], Para [ Str "blank`:myrole:" ] ]
```
Backslash escape behaves properly in interpreted roles:
@ -18,8 +17,11 @@ Backslash escape behaves properly in interpreted roles:
`hi\ there`:code:
^D
[Para [Superscript [Str "hithere"]]
,Para [Code ("",[],[]) "hi\\ there"]]
[ Para
[ Superscript [ Str "hithere" ] ]
, Para
[ Code ( "", [], [] ) "hi\\ there" ]
]
```
Backtick followed by alphanumeric doesn't end the span:
@ -27,7 +29,11 @@ Backtick followed by alphanumeric doesn't end the span:
% pandoc -f rst -t native
`hi`there`:myrole:
^D
[Para [Code ("",["interpreted-text"],[("role","myrole")]) "hi`there"]]
[ Para
[ Code
( "", [ "interpreted-text" ], [ ( "role", "myrole" ) ] ) "hi`there"
]
]
```
Newline is okay, as long as not blank:
@ -36,7 +42,11 @@ Newline is okay, as long as not blank:
`hi
there`:myrole:
^D
[Para [Code ("",["interpreted-text"],[("role","myrole")]) "hi\nthere"]]
[ Para
[ Code
( "", [ "interpreted-text" ], [ ( "role", "myrole" ) ] ) "hi\nthere"
]
]
```
Use span for title-reference:
@ -44,5 +54,5 @@ Use span for title-reference:
% pandoc -f rst -t native
`default`
^D
[Para [Span ("",["title-ref"],[]) [Str "default"]]]
[ Para [ Span ( "", [ "title-ref" ], [] ) [ Str "default" ] ] ]
```

View file

@ -5,6 +5,17 @@ foo:
- bar: bam
...
^D
Pandoc (Meta {unMeta = fromList [("foo",MetaList [MetaMap (fromList [("bar",MetaInlines [Str "bam"])])])]})
[]
Pandoc
( Meta
{ unMeta = fromList
[
( "foo"
, MetaList
[ MetaMap
( fromList [ ( "bar", MetaInlines [ Str "bam" ] ) ] )
]
)
]
}
) []
```

View file

@ -4,8 +4,10 @@
foo: 42
...
^D
Pandoc (Meta {unMeta = fromList [("foo",MetaInlines [Str "42"])]})
[]
Pandoc
( Meta
{ unMeta = fromList [ ( "foo", MetaInlines [ Str "42" ] ) ] }
) []
```
```
@ -14,8 +16,8 @@ Pandoc (Meta {unMeta = fromList [("foo",MetaInlines [Str "42"])]})
foo: true
...
^D
Pandoc (Meta {unMeta = fromList [("foo",MetaBool True)]})
[]
Pandoc
( Meta { unMeta = fromList [ ( "foo", MetaBool True ) ] } ) []
```
```
@ -24,8 +26,8 @@ Pandoc (Meta {unMeta = fromList [("foo",MetaBool True)]})
foo: True
...
^D
Pandoc (Meta {unMeta = fromList [("foo",MetaBool True)]})
[]
Pandoc
( Meta { unMeta = fromList [ ( "foo", MetaBool True ) ] } ) []
```
```
@ -34,8 +36,8 @@ Pandoc (Meta {unMeta = fromList [("foo",MetaBool True)]})
foo: FALSE
...
^D
Pandoc (Meta {unMeta = fromList [("foo",MetaBool False)]})
[]
Pandoc
( Meta { unMeta = fromList [ ( "foo", MetaBool False ) ] } ) []
```
```
@ -44,7 +46,9 @@ Pandoc (Meta {unMeta = fromList [("foo",MetaBool False)]})
foo: no
...
^D
Pandoc (Meta {unMeta = fromList [("foo",MetaInlines [Str "no"])]})
[]
Pandoc
( Meta
{ unMeta = fromList [ ( "foo", MetaInlines [ Str "no" ] ) ] }
) []
```

View file

@ -2,20 +2,38 @@
% pandoc -f latex -t native
\url{http://example.com/foo%20bar.htm}
^D
[Para [Link ("",[],[]) [Str "http://example.com/foo%20bar.htm"] ("http://example.com/foo%20bar.htm","")]]
[ Para
[ Link
( "", [], [] )
[ Str "http://example.com/foo%20bar.htm" ]
( "http://example.com/foo%20bar.htm", "" )
]
]
```
```
% pandoc -f latex -t native
\url{http://example.com/foo{bar}.htm}
^D
[Para [Link ("",[],[]) [Str "http://example.com/foo{bar}.htm"] ("http://example.com/foo{bar}.htm","")]]
[ Para
[ Link
( "", [], [] )
[ Str "http://example.com/foo{bar}.htm" ]
( "http://example.com/foo{bar}.htm", "" )
]
]
```
```
% pandoc -f latex -t native
\href{http://example.com/foo%20bar}{Foobar}
^D
[Para [Link ("",[],[]) [Str "Foobar"] ("http://example.com/foo%20bar","")]]
[ Para
[ Link
( "", [], [] )
[ Str "Foobar" ]
( "http://example.com/foo%20bar", "" )
]
]
```

View file

@ -2,5 +2,5 @@
% pandoc -f latex -t native
\l
^D
[Para [Str "\322"]]
[ Para [ Str "\322" ] ]
```

View file

@ -2,5 +2,15 @@
% pandoc -f html -t native
x<a href="/foo"> leading trailing space </a>x
^D
[Plain [Str "x",Space,Link ("",[],[]) [Str "leading",Space,Str "trailing",Space,Str "space"] ("/foo",""),Space,Str "x"]]
[ Plain
[ Str "x"
, Space
, Link
( "", [], [] )
[ Str "leading", Space, Str "trailing", Space, Str "space" ]
( "/foo", "" )
, Space
, Str "x"
]
]
```

View file

@ -2,21 +2,29 @@
% pandoc -f latex -t native
\enquote*{hi}
^D
[Para [Quoted SingleQuote [Str "hi"]]]
[ Para [ Quoted SingleQuote [ Str "hi" ] ] ]
```
```
% pandoc -f latex -t native
\foreignquote{italian}{hi}
^D
[Para [Quoted DoubleQuote [Span ("",[],[("lang","it")]) [Str "hi"]]]]
[ Para
[ Quoted DoubleQuote
[ Span ( "", [], [ ( "lang", "it" ) ] ) [ Str "hi" ] ]
]
]
```
```
% pandoc -f latex -t native
\hyphenquote*{italian}{hi}
^D
[Para [Quoted SingleQuote [Span ("",[],[("lang","it")]) [Str "hi"]]]]
[ Para
[ Quoted SingleQuote
[ Span ( "", [], [ ( "lang", "it" ) ] ) [ Str "hi" ] ]
]
]
```
```
@ -25,10 +33,13 @@ Lorem ipsum
\blockquote{dolor sit amet}
consectetuer.
^D
[Para [Str "Lorem",Space,Str "ipsum"]
,BlockQuote
[Para [Str "dolor",Space,Str "sit",Space,Str "amet"]]
,Para [Str "consectetuer."]]
[ Para
[ Str "Lorem", Space, Str "ipsum" ]
, BlockQuote
[ Para [ Str "dolor", Space, Str "sit", Space, Str "amet" ] ]
, Para
[ Str "consectetuer." ]
]
```
```
@ -37,11 +48,28 @@ Lorem ipsum
\blockcquote[198]{Knu86}{dolor sit amet}
consectetuer.
^D
[Para [Str "Lorem",Space,Str "ipsum"]
,BlockQuote
[Para [Str "dolor",Space,Str "sit",Space,Str "amet"]
,Para [Cite [Citation {citationId = "Knu86", citationPrefix = [], citationSuffix = [Str "198"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] []]]
,Para [Str "consectetuer."]]
[ Para
[ Str "Lorem", Space, Str "ipsum" ]
, BlockQuote
[ Para
[ Str "dolor", Space, Str "sit", Space, Str "amet" ]
, Para
[ Cite
[ Citation
{ citationId = "Knu86"
, citationPrefix = []
, citationSuffix =
[ Str "198" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
] []
]
]
, Para
[ Str "consectetuer." ]
]
```
```
@ -50,10 +78,15 @@ Lorem ipsum
\foreignblockquote{italian}{dolor sit amet}
consectetuer.
^D
[Para [Str "Lorem",Space,Str "ipsum"]
,BlockQuote
[Div ("",[],[("lang","it")])
[Para [Str "dolor",Space,Str "sit",Space,Str "amet"]]]
,Para [Str "consectetuer."]]
[ Para
[ Str "Lorem", Space, Str "ipsum" ]
, BlockQuote
[ Div
( "", [], [ ( "lang", "it" ) ] )
[ Para [ Str "dolor", Space, Str "sit", Space, Str "amet" ] ]
]
, Para
[ Str "consectetuer." ]
]
```

View file

@ -5,5 +5,16 @@ This is broken_.
.. ***** REFERENCES FOLLOW *****
.. _broken: http://google.com
^D
[Para [Str "This",Space,Str "is",Space,Link ("",[],[]) [Str "broken"] ("http://google.com",""),Str "."]]
[ Para
[ Str "This"
, Space
, Str "is"
, Space
, Link
( "", [], [] )
[ Str "broken" ]
( "http://google.com", "" )
, Str "."
]
]
```

View file

@ -2,12 +2,12 @@
% pandoc -f html -t native
My <script type="math/tex">\mathcal{D}</script>
^D
[Plain [Str "My",Space,Math InlineMath "\\mathcal{D}"]]
[ Plain [ Str "My", Space, Math InlineMath "\\mathcal{D}" ] ]
```
```
% pandoc -f html -t native
<script type="math/tex; mode=display">\mathcal{D}</script>
^D
[Plain [Math DisplayMath "\\mathcal{D}"]]
[ Plain [ Math DisplayMath "\\mathcal{D}" ] ]
```

View file

@ -7,8 +7,9 @@
V = \frac{K}{r^2}
^D
[Div ("tgtmath",[],[])
[BlockQuote
[Para [Math DisplayMath "V = \\frac{K}{r^2}"]]]]
[ Div
( "tgtmath", [], [] )
[ BlockQuote [ Para [ Math DisplayMath "V = \\frac{K}{r^2}" ] ] ]
]
```

View file

@ -2,47 +2,225 @@
% pandoc -f latex -t native
\cites(Multiprenote)(multipostnote)[23][42]{Knu86}[65]{Nie72}
^D
[Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "Multiprenote",Space,Str "23"], citationSuffix = [Str "42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "Nie72", citationPrefix = [], citationSuffix = [Str "65",Str ",",Space,Str "multipostnote"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cites(Multiprenote)(multipostnote)[23][42]{Knu86}[65]{Nie72}"]]]
[ Para
[ Cite
[ Citation
{ citationId = "Knu86"
, citationPrefix =
[ Str "Multiprenote", Space, Str "23" ]
, citationSuffix =
[ Str "42" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
, Citation
{ citationId = "Nie72"
, citationPrefix = []
, citationSuffix =
[ Str "65", Str ",", Space, Str "multipostnote" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
]
[ RawInline
( Format "latex" ) "\\cites(Multiprenote)(multipostnote)[23][42]{Knu86}[65]{Nie72}"
]
]
]
```
```
% pandoc -f latex -t native
\cites(Multiprenote)()[23][42]{Knu86}[65]{Nie72}
^D
[Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "Multiprenote",Space,Str "23"], citationSuffix = [Str "42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "Nie72", citationPrefix = [], citationSuffix = [Str "65"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cites(Multiprenote)()[23][42]{Knu86}[65]{Nie72}"]]]
[ Para
[ Cite
[ Citation
{ citationId = "Knu86"
, citationPrefix =
[ Str "Multiprenote", Space, Str "23" ]
, citationSuffix =
[ Str "42" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
, Citation
{ citationId = "Nie72"
, citationPrefix = []
, citationSuffix =
[ Str "65" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
]
[ RawInline
( Format "latex" ) "\\cites(Multiprenote)()[23][42]{Knu86}[65]{Nie72}"
]
]
]
```
```
% pandoc -f latex -t native
\cites()(multipostnote)[23][42]{Knu86}[65]{Nie72}
^D
[Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "23"], citationSuffix = [Str "42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "Nie72", citationPrefix = [], citationSuffix = [Str "65",Str ",",Space,Str "multipostnote"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cites()(multipostnote)[23][42]{Knu86}[65]{Nie72}"]]]
[ Para
[ Cite
[ Citation
{ citationId = "Knu86"
, citationPrefix =
[ Str "23" ]
, citationSuffix =
[ Str "42" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
, Citation
{ citationId = "Nie72"
, citationPrefix = []
, citationSuffix =
[ Str "65", Str ",", Space, Str "multipostnote" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
]
[ RawInline
( Format "latex" ) "\\cites()(multipostnote)[23][42]{Knu86}[65]{Nie72}"
]
]
]
```
```
% pandoc -f latex -t native
\cites()()[23][42]{Knu86}[65]{Nie72}
^D
[Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "23"], citationSuffix = [Str "42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "Nie72", citationPrefix = [], citationSuffix = [Str "65"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cites()()[23][42]{Knu86}[65]{Nie72}"]]]
[ Para
[ Cite
[ Citation
{ citationId = "Knu86"
, citationPrefix =
[ Str "23" ]
, citationSuffix =
[ Str "42" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
, Citation
{ citationId = "Nie72"
, citationPrefix = []
, citationSuffix =
[ Str "65" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
]
[ RawInline
( Format "latex" ) "\\cites()()[23][42]{Knu86}[65]{Nie72}"
]
]
]
```
```
% pandoc -f latex -t native
\cites(multipostnote)[23][42]{Knu86}[65]{Nie72}
^D
[Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "23"], citationSuffix = [Str "42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "Nie72", citationPrefix = [], citationSuffix = [Str "65",Str ",",Space,Str "multipostnote"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cites(multipostnote)[23][42]{Knu86}[65]{Nie72}"]]]
[ Para
[ Cite
[ Citation
{ citationId = "Knu86"
, citationPrefix =
[ Str "23" ]
, citationSuffix =
[ Str "42" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
, Citation
{ citationId = "Nie72"
, citationPrefix = []
, citationSuffix =
[ Str "65", Str ",", Space, Str "multipostnote" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
]
[ RawInline
( Format "latex" ) "\\cites(multipostnote)[23][42]{Knu86}[65]{Nie72}"
]
]
]
```
```
% pandoc -f latex -t native
\cites(Multiprenote)(multipostnote){Knu86}
^D
[Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "Multiprenote"], citationSuffix = [Str ",",Space,Str "multipostnote"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\cites(Multiprenote)(multipostnote){Knu86}"]]]
[ Para
[ Cite
[ Citation
{ citationId = "Knu86"
, citationPrefix =
[ Str "Multiprenote" ]
, citationSuffix =
[ Str ",", Space, Str "multipostnote" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
]
[ RawInline
( Format "latex" ) "\\cites(Multiprenote)(multipostnote){Knu86}"
]
]
]
```
```
% pandoc -f latex -t native
\footcites(Multiprenote)(multipostnote)[23][42]{Knu86}[65]{Nie72}
^D
[Para [Note [Para [Cite [Citation {citationId = "Knu86", citationPrefix = [Str "Multiprenote",Space,Str "23"], citationSuffix = [Str "42"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0},Citation {citationId = "Nie72", citationPrefix = [], citationSuffix = [Str "65",Str ",",Space,Str "multipostnote"], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [RawInline (Format "latex") "\\footcites(Multiprenote)(multipostnote)[23][42]{Knu86}[65]{Nie72}"],Str "."]]]]
[ Para
[ Note
[ Para
[ Cite
[ Citation
{ citationId = "Knu86"
, citationPrefix =
[ Str "Multiprenote", Space, Str "23" ]
, citationSuffix =
[ Str "42" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
, Citation
{ citationId = "Nie72"
, citationPrefix = []
, citationSuffix =
[ Str "65", Str ",", Space, Str "multipostnote" ]
, citationMode = NormalCitation
, citationNoteNum = 0
, citationHash = 0
}
]
[ RawInline
( Format "latex" ) "\\footcites(Multiprenote)(multipostnote)[23][42]{Knu86}[65]{Nie72}"
]
, Str "."
]
]
]
]
```

View file

@ -2,5 +2,5 @@
% pandoc -f latex -t native
\includegraphics{lalune}
^D
[Para [Image ("",[],[]) [Str "image"] ("lalune.jpg","")]]
[ Para [ Image ( "", [], [] ) [ Str "image" ] ( "lalune.jpg", "" ) ] ]
```

View file

@ -13,18 +13,35 @@
</tbody>
</table>
^D
[Table ("",[],[]) (Caption Nothing
[])
[(AlignDefault,ColWidthDefault)]
(TableHead ("",[],[])
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Name"]]]])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Accounts"]]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [] )
[ ( AlignDefault, ColWidthDefault ) ]
( TableHead
( "", [], [] )
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Name" ] ]
]
]
)
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Accounts" ] ]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```

View file

@ -10,16 +10,24 @@
</tbody>
</table>
^D
[Table ("",[],[]) (Caption Nothing
[])
[(AlignDefault,ColWidthDefault)]
(TableHead ("",[],[])
[])
[(TableBody ("",[],[]) (RowHeadColumns 0)
[]
[Row ("",[],[])
[Cell ("",[],[]) AlignDefault (RowSpan 1) (ColSpan 1)
[Plain [Str "Cell"]]]])]
(TableFoot ("",[],[])
[])]
[ Table
( "", [], [] )
( Caption Nothing [] )
[ ( AlignDefault, ColWidthDefault ) ]
( TableHead ( "", [], [] ) [] )
[ TableBody
( "", [], [] )
( RowHeadColumns 0 ) []
[ Row
( "", [], [] )
[ Cell
( "", [], [] ) AlignDefault
( RowSpan 1 )
( ColSpan 1 )
[ Plain [ Str "Cell" ] ]
]
]
]
( TableFoot ( "", [], [] ) [] )
]
```

View file

@ -2,12 +2,26 @@
% pandoc -t native
(@citation
^D
[Para [Str "(",Cite [Citation {citationId = "citation", citationPrefix = [], citationSuffix = [], citationMode = AuthorInText, citationNoteNum = 1, citationHash = 0}] [Str "@citation"]]]
[ Para
[ Str "("
, Cite
[ Citation
{ citationId = "citation"
, citationPrefix = []
, citationSuffix = []
, citationMode = AuthorInText
, citationNoteNum = 1
, citationHash = 0
}
]
[ Str "@citation" ]
]
]
```
```
% pandoc -t native
('asd')
^D
[Para [Str "(",Quoted SingleQuote [Str "asd"],Str ")"]]
[ Para [ Str "(", Quoted SingleQuote [ Str "asd" ], Str ")" ] ]
```

View file

@ -22,8 +22,21 @@ unsafePerformIO main
(+ 2 2)
#+end_src
^D
[CodeBlock ("",["commonlisp","numberLines"],[("org-language","lisp"),("startFrom","20")]) "(+ 1 1)\n"
,CodeBlock ("",["commonlisp","numberLines","continuedSourceBlock"],[("org-language","lisp"),("startFrom","10")]) "(+ 2 2)\n"]
[ CodeBlock
( ""
,
[ "commonlisp", "numberLines" ]
,
[ ( "org-language", "lisp" ), ( "startFrom", "20" ) ]
) "(+ 1 1)\n"
, CodeBlock
( ""
,
[ "commonlisp", "numberLines", "continuedSourceBlock" ]
,
[ ( "org-language", "lisp" ), ( "startFrom", "10" ) ]
) "(+ 2 2)\n"
]
```
```

Some files were not shown because too many files have changed in this diff Show more