summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README59
-rw-r--r--appveyor.yml42
m---------data/templates14
-rw-r--r--pandoc.cabal9
-rw-r--r--pandoc.hs36
-rw-r--r--src/Text/Pandoc.hs2
-rw-r--r--src/Text/Pandoc/Options.hs2
-rw-r--r--src/Text/Pandoc/Readers/MediaWiki.hs2
-rw-r--r--src/Text/Pandoc/Readers/Org.hs407
-rw-r--r--src/Text/Pandoc/Readers/Org/ParserState.hs207
-rw-r--r--src/Text/Pandoc/Writers/Docbook.hs21
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs13
-rw-r--r--src/Text/Pandoc/Writers/Org.hs2
-rw-r--r--tests/Tests/Old.hs3
-rw-r--r--tests/Tests/Readers/Org.hs35
-rw-r--r--tests/mediawiki-reader.native5
-rw-r--r--tests/mediawiki-reader.wiki8
-rw-r--r--tests/tables.docbook5432
-rw-r--r--tests/tables.latex144
-rw-r--r--tests/writer.docbook51395
-rw-r--r--windows/stack-appveyor.yaml20
21 files changed, 2491 insertions, 367 deletions
diff --git a/README b/README
index b589bc03a..df18fcfb1 100644
--- a/README
+++ b/README
@@ -273,26 +273,26 @@ General options
(LaTeX), `beamer` (LaTeX beamer slide show), `context` (ConTeXt),
`man` (groff man), `mediawiki` (MediaWiki markup), `dokuwiki`
(DokuWiki markup), `textile` (Textile), `org` (Emacs Org mode),
- `texinfo` (GNU Texinfo), `opml` (OPML), `docbook` (DocBook),
- `opendocument` (OpenDocument), `odt` (OpenOffice text document),
- `docx` (Word docx), `haddock` (Haddock markup), `rtf` (rich text
- format), `epub` (EPUB v2 book), `epub3` (EPUB v3), `fb2`
- (FictionBook2 e-book), `asciidoc` (AsciiDoc), `icml` (InDesign
- ICML), `tei` (TEI Simple), `slidy` (Slidy HTML and javascript slide
- show), `slideous` (Slideous HTML and javascript slide show),
- `dzslides` (DZSlides HTML5 + javascript slide show), `revealjs`
- (reveal.js HTML5 + javascript slide show), `s5` (S5 HTML and javascript
- slide show), or the path of a custom lua writer (see [Custom
- writers], below). Note that `odt`, `epub`, and
- `epub3` output will not be directed to *stdout*; an output
- filename must be specified using the `-o/--output` option. If
- `+lhs` is appended to `markdown`, `rst`, `latex`, `beamer`,
- `html`, or `html5`, the output will be rendered as literate
- Haskell source: see [Literate Haskell
- support], below. Markdown syntax
- extensions can be individually enabled or disabled by appending
- `+EXTENSION` or `-EXTENSION` to the format name, as described
- above under `-f`.
+ `texinfo` (GNU Texinfo), `opml` (OPML), `docbook` (DocBook 4),
+ `docbook5` (DocBook 5), `opendocument` (OpenDocument), `odt`
+ (OpenOffice text document), `docx` (Word docx), `haddock`
+ (Haddock markup), `rtf` (rich text format), `epub` (EPUB v2
+ book), `epub3` (EPUB v3), `fb2` (FictionBook2 e-book),
+ `asciidoc` (AsciiDoc), `icml` (InDesign ICML), `tei` (TEI
+ Simple), `slidy` (Slidy HTML and javascript slide show),
+ `slideous` (Slideous HTML and javascript slide show),
+ `dzslides` (DZSlides HTML5 + javascript slide show),
+ `revealjs` (reveal.js HTML5 + javascript slide show), `s5`
+ (S5 HTML and javascript slide show), or the path of a custom
+ lua writer (see [Custom writers], below). Note that `odt`,
+ `epub`, and `epub3` output will not be directed to *stdout*;
+ an output filename must be specified using the `-o/--output`
+ option. If `+lhs` is appended to `markdown`, `rst`, `latex`,
+ `beamer`, `html`, or `html5`, the output will be rendered as
+ literate Haskell source: see [Literate Haskell support],
+ below. Markdown syntax extensions can be individually
+ enabled or disabled by appending `+EXTENSION` or
+ `-EXTENSION` to the format name, as described above under `-f`.
`-o` *FILE*, `--output=`*FILE*
@@ -547,7 +547,7 @@ General writer options
: Include an automatically generated table of contents (or, in
the case of `latex`, `context`, `docx`, and `rst`, an instruction to create
one) in the output document. This option has no effect on `man`,
- `docbook`, `slidy`, `slideous`, `s5`, or `odt` output.
+ `docbook`, `docbook5`, `slidy`, `slideous`, `s5`, or `odt` output.
`--toc-depth=`*NUMBER*
@@ -909,7 +909,7 @@ Math rendering in HTML
`--mathml`[`=`*URL*]
-: Convert TeX math to [MathML] (in `docbook` as well as `html` and `html5`).
+: Convert TeX math to [MathML] (in `docbook`, `docbook5`, `html` and `html5`).
In standalone `html` output, a small javascript (or a link to such a
script if a *URL* is supplied) will be inserted that allows the MathML to
be viewed on some browsers.
@@ -1591,21 +1591,26 @@ CSS.
#### Extension: `implicit_header_references` ####
Pandoc behaves as if reference links have been defined for each header.
-So, instead of
+So, to link to a header
- [header identifiers](#header-identifiers-in-html)
+ # Header identifiers in HTML
you can simply write
- [header identifiers]
+ [Header identifiers in HTML]
or
- [header identifiers][]
+ [Header identifiers in HTML][]
or
- [the section on header identifiers][header identifiers]
+ [the section on header identifiers][header identifiers in
+ HTML]
+
+instead of giving the identifier explicitly:
+
+ [Header identifiers in HTML](#header-identifiers-in-html)
If there are multiple headers with identical text, the corresponding
reference will link to the first one only, and you will need to use explicit
diff --git a/appveyor.yml b/appveyor.yml
index f2fe828fa..03075c698 100644
--- a/appveyor.yml
+++ b/appveyor.yml
@@ -1,19 +1,37 @@
-cache:
-- "c:\\sr" # stack root, short paths == fewer problems
+clone_folder: "c:\\stack"
+environment:
+ global:
+ STACK_ROOT: "c:\\sr"
+ STACK_YAML: "c:\\stack\\windows\\stack-appveyor.yaml"
+
+cache:
+ - "c:\\sr" # stack root, short paths == fewer problems
+ - '%LOCALAPPDATA%\Programs\stack' # even less to install...
+
build: off
+install:
+ - curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386
+ - 7z x stack.zip stack.exe
+ - stack setup > nul
+
before_test:
-- curl -ostack.zip -L --insecure http://www.stackage.org/stack/windows-i386
-- 7z x stack.zip stack.exe
+ # the stack install already fails without the templates...
+ - git submodule update --init
+ # set PATH to where the hsb2hs binary is copied to
+ - cmd: set "PATH=%PATH%;%APPDATA%\\local\\bin"
+ - stack install hsb2hs
-clone_folder: "c:\\stack"
-environment:
- global:
- STACK_ROOT: "c:\\sr"
test_script:
-- stack setup > nul
-# The ugly echo "" hack is to avoid complaints about 0 being an invalid file
-# descriptor
-- echo "" | stack --no-terminal test
+ # The ugly echo "" hack is to avoid complaints about 0 being an invalid file
+ # descriptor
+ - echo "" | stack --no-terminal test
+
+after_test:
+ - ps: 7z a "pandoc.zip" "$(.\\stack.exe path --local-install-root)\\bin\\pandoc*.exe"
+
+artifacts:
+ - path: pandoc.zip
+ name: exe
diff --git a/data/templates b/data/templates
-Subproject d39b2207f98e8a6c6f91b0498c183069a0aa7c9
+Subproject 63471c3b8cc2e30ccd92f46b2bc40521960fa06
diff --git a/pandoc.cabal b/pandoc.cabal
index eebcb6a2c..d1d623060 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -1,5 +1,5 @@
Name: pandoc
-Version: 1.17.0.3
+Version: 1.17.1
Cabal-Version: >= 1.10
Build-Type: Custom
License: GPL
@@ -39,6 +39,7 @@ Data-Files:
data/templates/default.html
data/templates/default.html5
data/templates/default.docbook
+ data/templates/default.docbook5
data/templates/default.tei
data/templates/default.beamer
data/templates/default.opendocument
@@ -145,6 +146,7 @@ Extra-Source-Files:
tests/s5-inserts.html
tests/tables.context
tests/tables.docbook
+ tests/tables.docbook5
tests/tables.dokuwiki
tests/tables.icml
tests/tables.html
@@ -168,6 +170,7 @@ Extra-Source-Files:
tests/writer.latex
tests/writer.context
tests/writer.docbook
+ tests/writer.docbook5
tests/writer.html
tests/writer.man
tests/writer.markdown
@@ -390,6 +393,7 @@ Library
Text.Pandoc.Readers.Odt.Generic.XMLConverter,
Text.Pandoc.Readers.Odt.Arrows.State,
Text.Pandoc.Readers.Odt.Arrows.Utils,
+ Text.Pandoc.Readers.Org.ParserState,
Text.Pandoc.Writers.Shared,
Text.Pandoc.Asciify,
Text.Pandoc.MIME,
@@ -421,7 +425,8 @@ Executable pandoc
aeson >= 0.7.0.5 && < 0.12,
yaml >= 0.8.8.2 && < 0.9,
containers >= 0.1 && < 0.6,
- HTTP >= 4000.0.5 && < 4000.4
+ HTTP >= 4000.0.5 && < 4000.4,
+ process >= 1.0 && < 1.5
if flag(network-uri)
Build-Depends: network-uri >= 2.6 && < 2.7, network >= 2.6
else
diff --git a/pandoc.hs b/pandoc.hs
index e8a971de7..78dcd6840 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE CPP, TupleSections #-}
+{-# LANGUAGE CPP, TupleSections, ScopedTypeVariables #-}
{-
Copyright (C) 2006-2016 John MacFarlane <jgm@berkeley.edu>
@@ -52,7 +52,14 @@ import Data.Char ( toLower, toUpper )
import Data.List ( delete, intercalate, isPrefixOf, isSuffixOf, sort )
import System.Directory ( getAppUserDataDirectory, findExecutable,
doesFileExist, Permissions(..), getPermissions )
-import System.IO ( stdout, stderr )
+import System.Process ( shell, CreateProcess(..),
+ waitForProcess, StdStream(CreatePipe) )
+#if MIN_VERSION_process(1,2,1)
+import System.Process ( createProcess_ )
+#else
+import System.Process.Internals ( createProcess_ )
+#endif
+import System.IO ( stdout, stderr, hClose )
import System.IO.Error ( isDoesNotExistError )
import qualified Control.Exception as E
import Control.Exception.Extensible ( throwIO )
@@ -836,7 +843,7 @@ options =
, Option "" ["mathjax"]
(OptArg
(\arg opt -> do
- let url' = fromMaybe "https://cdn.mathjax.org/mathjax/latest/MathJax.js?config=TeX-AMS-MML_HTMLorMML" arg
+ let url' = fromMaybe "https://cdn.mathjax.org/mathjax/latest/MathJax.js?config=TeX-AMS_CHTML-full" arg
return opt { optHTMLMathMethod = MathJax url'})
"URL")
"" -- "Use MathJax for HTML math"
@@ -1401,8 +1408,8 @@ convertWithOpts opts args = do
_ | html5Output -> "wkhtmltopdf"
_ -> latexEngine
-- check for pdf creating program
- mbPdfProg <- findExecutable pdfprog
- when (isNothing mbPdfProg) $
+ progExists <- checkProg pdfprog
+ when (not progExists) $
err 41 $ pdfprog ++ " not found. " ++
pdfprog ++ " is needed for pdf output."
@@ -1424,3 +1431,22 @@ convertWithOpts opts args = do
handleEntities = if htmlFormat && ascii
then toEntities
else id
+
+-- Check for existence of prog by doing prog --version.
+checkProg :: String -> IO Bool
+checkProg "" = return False
+checkProg prog = E.handle handleErr $ do
+ (_,Just o,Just e,p) <- createProcess_ "system"
+ (shell (prog ++ " --version")){
+ delegate_ctlc = True,
+ std_out = CreatePipe,
+ std_err = CreatePipe
+ }
+ ec <- waitForProcess p
+ hClose o
+ hClose e
+ if ec == ExitSuccess
+ then return True
+ else return False
+ where handleErr :: E.SomeException -> IO Bool
+ handleErr _ = return False
diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs
index b67a53f5b..0330c46e2 100644
--- a/src/Text/Pandoc.hs
+++ b/src/Text/Pandoc.hs
@@ -291,6 +291,8 @@ writers = [
writeHtmlString o{ writerSlideVariant = RevealJsSlides
, writerHtml5 = True })
,("docbook" , PureStringWriter writeDocbook)
+ ,("docbook5" , PureStringWriter $ \o ->
+ writeDocbook o{ writerDocbook5 = True })
,("opml" , PureStringWriter writeOPML)
,("opendocument" , PureStringWriter writeOpenDocument)
,("latex" , PureStringWriter writeLaTeX)
diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs
index 171210962..701cd8bd1 100644
--- a/src/Text/Pandoc/Options.hs
+++ b/src/Text/Pandoc/Options.hs
@@ -357,6 +357,7 @@ data WriterOptions = WriterOptions
, writerSourceURL :: Maybe String -- ^ Absolute URL + directory of 1st source file
, writerUserDataDir :: Maybe FilePath -- ^ Path of user data directory
, writerCiteMethod :: CiteMethod -- ^ How to print cites
+ , writerDocbook5 :: Bool -- ^ Produce DocBook5
, writerHtml5 :: Bool -- ^ Produce HTML5
, writerHtmlQTags :: Bool -- ^ Use @<q>@ tags for quotes in HTML
, writerBeamer :: Bool -- ^ Produce beamer LaTeX slide show
@@ -403,6 +404,7 @@ instance Default WriterOptions where
, writerSourceURL = Nothing
, writerUserDataDir = Nothing
, writerCiteMethod = Citeproc
+ , writerDocbook5 = False
, writerHtml5 = False
, writerHtmlQTags = False
, writerBeamer = False
diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs
index 950497992..d3cee08e2 100644
--- a/src/Text/Pandoc/Readers/MediaWiki.hs
+++ b/src/Text/Pandoc/Readers/MediaWiki.hs
@@ -225,7 +225,7 @@ table = do
Nothing -> 1.0
caption <- option mempty tableCaption
optional rowsep
- hasheader <- option False $ True <$ (lookAhead (char '!'))
+ hasheader <- option False $ True <$ (lookAhead (skipSpaces *> char '!'))
(cellspecs',hdr) <- unzip <$> tableRow
let widths = map ((tableWidth *) . snd) cellspecs'
let restwidth = tableWidth - sum widths
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index 5e98be31d..ceab1e120 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -1,6 +1,5 @@
+{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE GeneralizedNewtypeDeriving #-}
-{-# LANGUAGE MultiParamTypeClasses, FlexibleContexts, FlexibleInstances #-}
{-
Copyright (C) 2014-2016 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
@@ -31,10 +30,10 @@ Conversion of org-mode formatted plain text to 'Pandoc' document.
module Text.Pandoc.Readers.Org ( readOrg ) where
import qualified Text.Pandoc.Builder as B
-import Text.Pandoc.Builder ( Inlines, Blocks, HasMeta(..),
- trimInlines )
+import Text.Pandoc.Builder ( Inlines, Blocks )
import Text.Pandoc.Definition
import Text.Pandoc.Compat.Monoid ((<>))
+import Text.Pandoc.Error
import Text.Pandoc.Options
import qualified Text.Pandoc.Parsing as P
import Text.Pandoc.Parsing hiding ( F, unF, askF, asksF, runF
@@ -42,22 +41,20 @@ import Text.Pandoc.Parsing hiding ( F, unF, askF, asksF, runF
, parseFromString, blanklines
)
import Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline)
+import Text.Pandoc.Readers.Org.ParserState
import Text.Pandoc.Shared (compactify', compactify'DL)
import Text.TeXMath (readTeX, writePandoc, DisplayType(..))
import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap
import Control.Arrow (first)
-import Control.Monad (foldM, guard, liftM, liftM2, mplus, mzero, when)
-import Control.Monad.Reader (Reader, runReader, ask, asks, local)
-import Data.Char (isAlphaNum, toLower)
-import Data.Default
+import Control.Monad (foldM, guard, mplus, mzero, when)
+import Control.Monad.Reader ( Reader, runReader )
+import Data.Char (isAlphaNum, isSpace, toLower)
import Data.List (intersperse, isPrefixOf, isSuffixOf)
import qualified Data.Map as M
-import qualified Data.Set as Set
import Data.Maybe (fromMaybe, isJust)
import Network.HTTP (urlEncode)
-import Text.Pandoc.Error
-- | Parse org-mode string and return a Pandoc document.
readOrg :: ReaderOptions -- ^ Reader options
@@ -65,132 +62,12 @@ readOrg :: ReaderOptions -- ^ Reader options
-> Either PandocError Pandoc
readOrg opts s = flip runReader def $ readWithM parseOrg def{ orgStateOptions = opts } (s ++ "\n\n")
-data OrgParserLocal = OrgParserLocal { orgLocalQuoteContext :: QuoteContext }
-
+-- | The parser used to read org files.
type OrgParser = ParserT [Char] OrgParserState (Reader OrgParserLocal)
-instance HasIdentifierList OrgParserState where
- extractIdentifierList = orgStateIdentifiers
- updateIdentifierList f s = s{ orgStateIdentifiers = f (orgStateIdentifiers s) }
-
-instance HasHeaderMap OrgParserState where
- extractHeaderMap = orgStateHeaderMap
- updateHeaderMap f s = s{ orgStateHeaderMap = f (orgStateHeaderMap s) }
-
-parseOrg :: OrgParser Pandoc
-parseOrg = do
- blocks' <- parseBlocks
- st <- getState
- let meta = runF (orgStateMeta' st) st
- let removeUnwantedBlocks = dropCommentTrees . filter (/= Null)
- return $ Pandoc meta $ removeUnwantedBlocks (B.toList $ runF blocks' st)
-
--- | Drop COMMENT headers and the document tree below those headers.
-dropCommentTrees :: [Block] -> [Block]
-dropCommentTrees [] = []
-dropCommentTrees (b:bs) =
- maybe (b:dropCommentTrees bs)
- (dropCommentTrees . flip dropUntilHeaderAboveLevel bs)
- (commentHeaderLevel b)
-
--- | Return the level of a header starting a comment or :noexport: tree and
--- Nothing otherwise.
-commentHeaderLevel :: Block -> Maybe Int
-commentHeaderLevel blk =
- case blk of
- (Header level _ ((Str "COMMENT"):_)) -> Just level
- (Header level _ title) | hasNoExportTag title -> Just level
- _ -> Nothing
- where
- hasNoExportTag :: [Inline] -> Bool
- hasNoExportTag = any isNoExportTag
-
- isNoExportTag :: Inline -> Bool
- isNoExportTag (Span ("", ["tag"], [("data-tag-name", "noexport")]) []) = True
- isNoExportTag _ = False
-
--- | Drop blocks until a header on or above the given level is seen
-dropUntilHeaderAboveLevel :: Int -> [Block] -> [Block]
-dropUntilHeaderAboveLevel n = dropWhile (not . isHeaderLevelLowerEq n)
-
-isHeaderLevelLowerEq :: Int -> Block -> Bool
-isHeaderLevelLowerEq n blk =
- case blk of
- (Header level _ _) -> n >= level
- _ -> False
-
--
--- Parser State for Org
+-- Functions acting on the parser state
--
-
-type OrgNoteRecord = (String, F Blocks)
-type OrgNoteTable = [OrgNoteRecord]
-
-type OrgBlockAttributes = M.Map String String
-
-type OrgLinkFormatters = M.Map String (String -> String)
-
--- | Org-mode parser state
-data OrgParserState = OrgParserState
- { orgStateOptions :: ReaderOptions
- , orgStateAnchorIds :: [String]
- , orgStateBlockAttributes :: OrgBlockAttributes
- , orgStateEmphasisCharStack :: [Char]
- , orgStateEmphasisNewlines :: Maybe Int
- , orgStateLastForbiddenCharPos :: Maybe SourcePos
- , orgStateLastPreCharPos :: Maybe SourcePos
- , orgStateLastStrPos :: Maybe SourcePos
- , orgStateLinkFormatters :: OrgLinkFormatters
- , orgStateMeta :: Meta
- , orgStateMeta' :: F Meta
- , orgStateNotes' :: OrgNoteTable
- , orgStateParserContext :: ParserContext
- , orgStateIdentifiers :: Set.Set String
- , orgStateHeaderMap :: M.Map Inlines String
- }
-
-instance Default OrgParserLocal where
- def = OrgParserLocal NoQuote
-
-instance HasReaderOptions OrgParserState where
- extractReaderOptions = orgStateOptions
-
-instance HasMeta OrgParserState where
- setMeta field val st =
- st{ orgStateMeta = setMeta field val $ orgStateMeta st }
- deleteMeta field st =
- st{ orgStateMeta = deleteMeta field $ orgStateMeta st }
-
-instance HasLastStrPosition OrgParserState where
- getLastStrPos = orgStateLastStrPos
- setLastStrPos pos st = st{ orgStateLastStrPos = Just pos }
-
-instance HasQuoteContext st (Reader OrgParserLocal) where
- getQuoteContext = asks orgLocalQuoteContext
- withQuoteContext q = local (\s -> s{orgLocalQuoteContext = q})
-
-instance Default OrgParserState where
- def = defaultOrgParserState
-
-defaultOrgParserState :: OrgParserState
-defaultOrgParserState = OrgParserState
- { orgStateOptions = def
- , orgStateAnchorIds = []
- , orgStateBlockAttributes = M.empty
- , orgStateEmphasisCharStack = []
- , orgStateEmphasisNewlines = Nothing
- , orgStateLastForbiddenCharPos = Nothing
- , orgStateLastPreCharPos = Nothing
- , orgStateLastStrPos = Nothing
- , orgStateLinkFormatters = M.empty
- , orgStateMeta = nullMeta
- , orgStateMeta' = return nullMeta
- , orgStateNotes' = []
- , orgStateParserContext = NullState
- , orgStateIdentifiers = Set.empty
- , orgStateHeaderMap = M.empty
- }
-
recordAnchorId :: String -> OrgParser ()
recordAnchorId i = updateState $ \s ->
s{ orgStateAnchorIds = i : (orgStateAnchorIds s) }
@@ -244,44 +121,117 @@ addToNotesTable note = do
oldnotes <- orgStateNotes' <$> getState
updateState $ \s -> s{ orgStateNotes' = note:oldnotes }
--- The version Text.Pandoc.Parsing cannot be used, as we need additional parts
--- of the state saved and restored.
-parseFromString :: OrgParser a -> String -> OrgParser a
-parseFromString parser str' = do
- oldLastPreCharPos <- orgStateLastPreCharPos <$> getState
- updateState $ \s -> s{ orgStateLastPreCharPos = Nothing }
- result <- P.parseFromString parser str'
- updateState $ \s -> s{ orgStateLastPreCharPos = oldLastPreCharPos }
- return result
+--
+-- Export Settings
+--
+exportSetting :: OrgParser ()
+exportSetting = choice
+ [ booleanSetting "^" setExportSubSuperscripts
+ , ignoredSetting "'"
+ , ignoredSetting "*"
+ , ignoredSetting "-"
+ , ignoredSetting ":"
+ , ignoredSetting "<"
+ , ignoredSetting "\\n"
+ , ignoredSetting "arch"
+ , ignoredSetting "author"
+ , ignoredSetting "c"
+ , ignoredSetting "creator"
+ , ignoredSetting "d"
+ , ignoredSetting "date"
+ , ignoredSetting "e"
+ , ignoredSetting "email"
+ , ignoredSetting "f"
+ , ignoredSetting "H"
+ , ignoredSetting "inline"
+ , ignoredSetting "num"
+ , ignoredSetting "p"
+ , ignoredSetting "pri"
+ , ignoredSetting "prop"
+ , ignoredSetting "stat"
+ , ignoredSetting "tags"
+ , ignoredSetting "tasks"
+ , ignoredSetting "tex"
+ , ignoredSetting "timestamp"
+ , ignoredSetting "title"
+ , ignoredSetting "toc"
+ , ignoredSetting "todo"
+ , ignoredSetting "|"
+ ] <?> "export setting"
+
+booleanSetting :: String -> ExportSettingSetter Bool -> OrgParser ()
+booleanSetting settingIdentifier setter = try $ do
+ string settingIdentifier
+ char ':'
+ value <- many nonspaceChar
+ let boolValue = case value of
+ "nil" -> False
+ "{}" -> False
+ _ -> True
+ updateState $ modifyExportSettings setter boolValue
+ignoredSetting :: String -> OrgParser ()
+ignoredSetting s = try (() <$ string s <* char ':' <* many nonspaceChar)
--
--- Adaptions and specializations of parsing utilities
+-- Parser
--
+parseOrg :: OrgParser Pandoc
+parseOrg = do
+ blocks' <- parseBlocks
+ st <- getState
+ let meta = runF (orgStateMeta' st) st
+ let removeUnwantedBlocks = dropCommentTrees . filter (/= Null)
+ return $ Pandoc meta $ removeUnwantedBlocks (B.toList $ runF blocks' st)
-newtype F a = F { unF :: Reader OrgParserState a
- } deriving (Monad, Applicative, Functor)
+-- | Drop COMMENT headers and the document tree below those headers.
+dropCommentTrees :: [Block] -> [Block]
+dropCommentTrees [] = []
+dropCommentTrees (b:bs) =
+ maybe (b:dropCommentTrees bs)
+ (dropCommentTrees . flip dropUntilHeaderAboveLevel bs)
+ (commentHeaderLevel b)
-runF :: F a -> OrgParserState -> a
-runF = runReader . unF
+-- | Return the level of a header starting a comment or :noexport: tree and
+-- Nothing otherwise.
+commentHeaderLevel :: Block -> Maybe Int
+commentHeaderLevel blk =
+ case blk of
+ (Header level _ ((Str "COMMENT"):_)) -> Just level
+ (Header level _ title) | hasNoExportTag title -> Just level
+ _ -> Nothing
+ where
+ hasNoExportTag :: [Inline] -> Bool
+ hasNoExportTag = any isNoExportTag
-askF :: F OrgParserState
-askF = F ask
+ isNoExportTag :: Inline -> Bool
+ isNoExportTag (Span ("", ["tag"], [("data-tag-name", "noexport")]) []) = True
+ isNoExportTag _ = False
-asksF :: (OrgParserState -> a) -> F a
-asksF f = F $ asks f
+-- | Drop blocks until a header on or above the given level is seen
+dropUntilHeaderAboveLevel :: Int -> [Block] -> [Block]
+dropUntilHeaderAboveLevel n = dropWhile (not . isHeaderLevelLowerEq n)
-instance Monoid a => Monoid (F a) where
- mempty = return mempty
- mappend = liftM2 mappend
- mconcat = fmap mconcat . sequence
+isHeaderLevelLowerEq :: Int -> Block -> Bool
+isHeaderLevelLowerEq n blk =
+ case blk of
+ (Header level _ _) -> n >= level
+ _ -> False
-trimInlinesF :: F Inlines -> F Inlines
-trimInlinesF = liftM trimInlines
-returnF :: a -> OrgParser (F a)
-returnF = return . return
+--
+-- Adaptions and specializations of parsing utilities
+--
+-- The version Text.Pandoc.Parsing cannot be used, as we need additional parts
+-- of the state saved and restored.
+parseFromString :: OrgParser a -> String -> OrgParser a
+parseFromString parser str' = do
+ oldLastPreCharPos <- orgStateLastPreCharPos <$> getState
+ updateState $ \s -> s{ orgStateLastPreCharPos = Nothing }
+ result <- P.parseFromString parser str'
+ updateState $ \s -> s{ orgStateLastPreCharPos = oldLastPreCharPos }
+ return result
-- | Like @Text.Parsec.Char.newline@, but causes additional state changes.
newline :: OrgParser Char
@@ -692,8 +642,9 @@ optionLine :: OrgParser ()
optionLine = try $ do
key <- metaKey
case key of
- "link" -> parseLinkFormat >>= uncurry addLinkFormat
- _ -> mzero
+ "link" -> parseLinkFormat >>= uncurry addLinkFormat
+ "options" -> () <$ sepBy spaces exportSetting
+ _ -> mzero
parseLinkFormat :: OrgParser ((String, String -> String))
parseLinkFormat = try $ do
@@ -774,9 +725,13 @@ data OrgTableRow = OrgContentRow (F [Blocks])
| OrgAlignRow [Alignment]
| OrgHlineRow
+-- OrgTable is strongly related to the pandoc table ADT. Using the same
+-- (i.e. pandoc-global) ADT would mean that the reader would break if the
+-- global structure was to be changed, which would be bad. The final table
+-- should be generated using a builder function. Column widths aren't
+-- implemented yet, so they are not tracked here.
data OrgTable = OrgTable
- { orgTableColumns :: Int
- , orgTableAlignments :: [Alignment]
+ { orgTableAlignments :: [Alignment]
, orgTableHeader :: [Blocks]
, orgTableRows :: [[Blocks]]
}
@@ -792,7 +747,7 @@ table = try $ do
orgToPandocTable :: OrgTable
-> Inlines
-> Blocks
-orgToPandocTable (OrgTable _ aligns heads lns) caption =
+orgToPandocTable (OrgTable aligns heads lns) caption =
B.table caption (zip aligns $ repeat 0) heads lns
tableStart :: OrgParser Char
@@ -803,18 +758,19 @@ tableRows = try $ many (tableAlignRow <|> tableHline <|> tableContentRow)
tableContentRow :: OrgParser OrgTableRow
tableContentRow = try $
- OrgContentRow . sequence <$> (tableStart *> manyTill tableContentCell newline)
+ OrgContentRow . sequence <$> (tableStart *> many1Till tableContentCell newline)
tableContentCell :: OrgParser (F Blocks)
tableContentCell = try $
- fmap B.plain . trimInlinesF . mconcat <$> many1Till inline endOfCell
-
-endOfCell :: OrgParser Char
-endOfCell = try $ char '|' <|> lookAhead newline
+ fmap B.plain . trimInlinesF . mconcat <$> manyTill inline endOfCell
tableAlignRow :: OrgParser OrgTableRow
-tableAlignRow = try $
- OrgAlignRow <$> (tableStart *> manyTill tableAlignCell newline)
+tableAlignRow = try $ do
+ tableStart
+ cells <- many1Till tableAlignCell newline
+ -- Empty rows are regular (i.e. content) rows, not alignment rows.
+ guard $ any (/= AlignDefault) cells
+ return $ OrgAlignRow cells
tableAlignCell :: OrgParser Alignment
tableAlignCell =
@@ -829,65 +785,61 @@ tableAlignCell =
where emptyCell = try $ skipSpaces *> endOfCell
tableAlignFromChar :: OrgParser Alignment
-tableAlignFromChar = try $ choice [ char 'l' *> return AlignLeft
- , char 'c' *> return AlignCenter
- , char 'r' *> return AlignRight
- ]
+tableAlignFromChar = try $
+ choice [ char 'l' *> return AlignLeft
+ , char 'c' *> return AlignCenter
+ , char 'r' *> return AlignRight
+ ]
tableHline :: OrgParser OrgTableRow
tableHline = try $
OrgHlineRow <$ (tableStart *> char '-' *> anyLine)
+endOfCell :: OrgParser Char
+endOfCell = try $ char '|' <|> lookAhead newline
+
rowsToTable :: [OrgTableRow]
-> F OrgTable
-rowsToTable = foldM (flip rowToContent) zeroTable
- where zeroTable = OrgTable 0 mempty mempty mempty
-
-normalizeTable :: OrgTable
- -> OrgTable
-normalizeTable (OrgTable cols aligns heads lns) =
- let aligns' = fillColumns aligns AlignDefault
- heads' = if heads == mempty
- then mempty
- else fillColumns heads (B.plain mempty)
- lns' = map (`fillColumns` B.plain mempty) lns
- fillColumns base padding = take cols $ base ++ repeat padding
- in OrgTable cols aligns' heads' lns'
+rowsToTable = foldM rowToContent emptyTable
+ where emptyTable = OrgTable mempty mempty mempty
+normalizeTable :: OrgTable -> OrgTable
+normalizeTable (OrgTable aligns heads rows) = OrgTable aligns' heads rows
+ where
+ refRow = if heads /= mempty
+ then heads
+ else if rows == mempty then mempty else head rows
+ cols = length refRow
+ fillColumns base padding = take cols $ base ++ repeat padding
+ aligns' = fillColumns aligns AlignDefault
-- One or more horizontal rules after the first content line mark the previous
-- line as a header. All other horizontal lines are discarded.
-rowToContent :: OrgTableRow
- -> OrgTable
- -> F OrgTable
-rowToContent OrgHlineRow t = maybeBodyToHeader t
-rowToContent (OrgAlignRow as) t = setLongestRow as =<< setAligns as t
-rowToContent (OrgContentRow rf) t = do
- rs <- rf
- setLongestRow rs =<< appendToBody rs t
-
-setLongestRow :: [a]
- -> OrgTable
- -> F OrgTable
-setLongestRow rs t =
- return t{ orgTableColumns = max (length rs) (orgTableColumns t) }
-
-maybeBodyToHeader :: OrgTable
- -> F OrgTable
-maybeBodyToHeader t = case t of
- OrgTable{ orgTableHeader = [], orgTableRows = b:[] } ->
- return t{ orgTableHeader = b , orgTableRows = [] }
- _ -> return t
-
-appendToBody :: [Blocks]
- -> OrgTable
+rowToContent :: OrgTable
+ -> OrgTableRow
-> F OrgTable
-appendToBody r t = return t{ orgTableRows = orgTableRows t ++ [r] }
+rowToContent orgTable row =
+ case row of
+ OrgHlineRow -> return singleRowPromotedToHeader
+ OrgAlignRow as -> return . setAligns $ as
+ OrgContentRow cs -> appendToBody cs
+ where
+ singleRowPromotedToHeader :: OrgTable
+ singleRowPromotedToHeader = case orgTable of
+ OrgTable{ orgTableHeader = [], orgTableRows = b:[] } ->
+ orgTable{ orgTableHeader = b , orgTableRows = [] }
+ _ -> orgTable
+
+ setAligns :: [Alignment] -> OrgTable
+ setAligns aligns = orgTable{ orgTableAlignments = aligns }
-setAligns :: [Alignment]
- -> OrgTable
- -> F OrgTable
-setAligns aligns t = return $ t{ orgTableAlignments = aligns }
+ appendToBody :: F [Blocks] -> F OrgTable
+ appendToBody frow = do
+ newRow <- frow
+ let oldRows = orgTableRows orgTable
+ -- NOTE: This is an inefficient O(n) operation. This should be changed
+ -- if performance ever becomes a problem.
+ return orgTable{ orgTableRows = oldRows ++ [newRow] }
--
@@ -1561,7 +1513,9 @@ subOrSuperExpr = try $
where enclosing (left, right) s = left : s ++ [right]
simpleSubOrSuperString :: OrgParser String
-simpleSubOrSuperString = try $
+simpleSubOrSuperString = try $ do
+ state <- getState
+ guard . exportSubSuperscripts . orgStateExportSettings $ state
choice [ string "*"
, mappend <$> option [] ((:[]) <$> oneOf "+-")
<*> many1 alphaNum
@@ -1581,14 +1535,14 @@ inlineLaTeX = try $ do
parseAsMathMLSym :: String -> Maybe Inlines
parseAsMathMLSym cs = B.str <$> MathMLEntityMap.getUnicode (clean cs)
- -- dropWhileEnd would be nice here, but it's not available before base 4.5
- where clean = reverse . dropWhile (`elem` ("{}" :: String)) . reverse . drop 1
+ -- drop initial backslash and any trailing "{}"
+ where clean = dropWhileEnd (`elem` ("{}" :: String)) . drop 1
state :: ParserState
state = def{ stateOptions = def{ readerParseRaw = True }}
- texMathToPandoc inp = (maybeRight $ readTeX inp) >>=
- writePandoc DisplayInline
+ texMathToPandoc :: String -> Maybe [Inline]
+ texMathToPandoc cs = (maybeRight $ readTeX cs) >>= writePandoc DisplayInline
maybeRight :: Either a b -> Maybe b
maybeRight = either (const Nothing) Just
@@ -1598,11 +1552,18 @@ inlineLaTeXCommand = try $ do
rest <- getInput
case runParser rawLaTeXInline def "source" rest of
Right (RawInline _ cs) -> do
- let len = length cs
+ -- drop any trailing whitespace, those are not be part of the command as
+ -- far as org mode is concerned.
+ let cmdNoSpc = dropWhileEnd isSpace cs
+ let len = length cmdNoSpc
count len anyChar
- return cs
+ return cmdNoSpc
_ -> mzero
+-- Taken from Data.OldList.
+dropWhileEnd :: (a -> Bool) -> [a] -> [a]
+dropWhileEnd p = foldr (\x xs -> if p x && null xs then [] else x : xs) []
+
smart :: OrgParser (F Inlines)
smart = do
getOption readerSmart >>= guard
diff --git a/src/Text/Pandoc/Readers/Org/ParserState.hs b/src/Text/Pandoc/Readers/Org/ParserState.hs
new file mode 100644
index 000000000..49cfa2be2
--- /dev/null
+++ b/src/Text/Pandoc/Readers/Org/ParserState.hs
@@ -0,0 +1,207 @@
+{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE GeneralizedNewtypeDeriving #-}
+{-# LANGUAGE MultiParamTypeClasses #-}
+{-
+Copyright (C) 2014-2016 Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+
+This program is free software; you can redistribute it and/or modify
+it under the terms of the GNU General Public License as published by
+the Free Software Foundation; either version 2 of the License, or
+(at your option) any later version.
+
+This program is distributed in the hope that it will be useful,
+but WITHOUT ANY WARRANTY; without even the implied warranty of
+MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
+GNU General Public License for more details.
+
+You should have received a copy of the GNU General Public License
+along with this program; if not, write to the Free Software
+Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
+-}
+
+{- |
+ Module : Text.Pandoc.Readers.Org.Options
+ Copyright : Copyright (C) 2014-2016 Albert Krewinkel
+ License : GNU GPL, version 2 or above
+
+ Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
+
+Define the Org-mode parser state.
+-}
+module Text.Pandoc.Readers.Org.ParserState
+ ( OrgParserState(..)
+ , OrgParserLocal(..)
+ , OrgNoteRecord
+ , F(..)
+ , askF
+ , asksF
+ , trimInlinesF
+ , runF
+ , returnF
+ , ExportSettingSetter
+ , exportSubSuperscripts
+ , setExportSubSuperscripts
+ , modifyExportSettings
+ ) where
+
+import Control.Monad (liftM, liftM2)
+import Control.Monad.Reader (Reader, runReader, ask, asks, local)
+
+import Data.Default (Default(..))
+import qualified Data.Map as M
+import qualified Data.Set as Set
+
+import Text.Pandoc.Builder ( Inlines, Blocks, HasMeta(..),
+ trimInlines )
+import Text.Pandoc.Definition ( Meta(..), nullMeta )
+import Text.Pandoc.Options ( ReaderOptions(..) )
+import Text.Pandoc.Parsing ( HasHeaderMap(..)
+ , HasIdentifierList(..)
+ , HasLastStrPosition(..)
+ , HasQuoteContext(..)
+ , HasReaderOptions(..)
+ , ParserContext(..)
+ , QuoteContext(..)
+ , SourcePos )
+
+-- | An inline note / footnote containing the note key and its (inline) value.
+type OrgNoteRecord = (String, F Blocks)
+-- | Table of footnotes
+type OrgNoteTable = [OrgNoteRecord]
+-- | Map of org block attributes (e.g. LABEL, CAPTION, NAME, etc)
+type OrgBlockAttributes = M.Map String String
+-- | Map of functions for link transformations. The map key is refers to the
+-- link-type, the corresponding function transforms the given link string.
+type OrgLinkFormatters = M.Map String (String -> String)
+
+-- | Export settings <http://orgmode.org/manual/Export-settings.html>
+-- These settings can be changed via OPTIONS statements.
+data ExportSettings = ExportSettings
+ { exportSubSuperscripts :: Bool -- ^ TeX-like syntax for sub- and superscripts
+ }
+
+-- | Org-mode parser state
+data OrgParserState = OrgParserState
+ { orgStateOptions :: ReaderOptions
+ , orgStateAnchorIds :: [String]
+ , orgStateBlockAttributes :: OrgBlockAttributes
+ , orgStateEmphasisCharStack :: [Char]
+ , orgStateEmphasisNewlines :: Maybe Int
+ , orgStateExportSettings :: ExportSettings
+ , orgStateLastForbiddenCharPos :: Maybe SourcePos
+ , orgStateLastPreCharPos :: Maybe SourcePos
+ , orgStateLastStrPos :: Maybe SourcePos
+ , orgStateLinkFormatters :: OrgLinkFormatters
+ , orgStateMeta :: Meta
+ , orgStateMeta' :: F Meta
+ , orgStateNotes' :: OrgNoteTable
+ , orgStateParserContext :: ParserContext
+ , orgStateIdentifiers :: Set.Set String
+ , orgStateHeaderMap :: M.Map Inlines String
+ }
+
+data OrgParserLocal = OrgParserLocal { orgLocalQuoteContext :: QuoteContext }
+
+instance Default OrgParserLocal where
+ def = OrgParserLocal NoQuote
+
+instance HasReaderOptions OrgParserState where
+ extractReaderOptions = orgStateOptions
+
+instance HasMeta OrgParserState where
+ setMeta field val st =
+ st{ orgStateMeta = setMeta field val $ orgStateMeta st }
+ deleteMeta field st =
+ st{ orgStateMeta = deleteMeta field $ orgStateMeta st }
+
+instance HasLastStrPosition OrgParserState where
+ getLastStrPos = orgStateLastStrPos
+ setLastStrPos pos st = st{ orgStateLastStrPos = Just pos }
+
+instance HasQuoteContext st (Reader OrgParserLocal) where
+ getQuoteContext = asks orgLocalQuoteContext
+ withQuoteContext q = local (\s -> s{orgLocalQuoteContext = q})
+
+instance HasIdentifierList OrgParserState where
+ extractIdentifierList = orgStateIdentifiers
+ updateIdentifierList f s = s{ orgStateIdentifiers = f (orgStateIdentifiers s) }
+
+instance HasHeaderMap OrgParserState where
+ extractHeaderMap = orgStateHeaderMap
+ updateHeaderMap f s = s{ orgStateHeaderMap = f (orgStateHeaderMap s) }
+
+instance Default ExportSettings where
+ def = defaultExportSettings
+
+instance Default OrgParserState where
+ def = defaultOrgParserState
+
+defaultOrgParserState :: OrgParserState
+defaultOrgParserState = OrgParserState
+ { orgStateOptions = def
+ , orgStateAnchorIds = []
+ , orgStateBlockAttributes = M.empty
+ , orgStateEmphasisCharStack = []
+ , orgStateEmphasisNewlines = Nothing
+ , orgStateExportSettings = def
+ , orgStateLastForbiddenCharPos = Nothing
+ , orgStateLastPreCharPos = Nothing
+ , orgStateLastStrPos = Nothing
+ , orgStateLinkFormatters = M.empty
+ , orgStateMeta = nullMeta
+ , orgStateMeta' = return nullMeta
+ , orgStateNotes' = []
+ , orgStateParserContext = NullState
+ , orgStateIdentifiers = Set.empty
+ , orgStateHeaderMap = M.empty
+ }
+
+defaultExportSettings :: ExportSettings
+defaultExportSettings = ExportSettings
+ { exportSubSuperscripts = True
+ }
+
+
+--
+-- Setter for exporting options
+--
+type ExportSettingSetter a = a -> ExportSettings -> ExportSettings
+
+setExportSubSuperscripts :: ExportSettingSetter Bool
+setExportSubSuperscripts val es = es { exportSubSuperscripts = val }
+
+-- | Modify a parser state
+modifyExportSettings :: ExportSettingSetter a -> a -> OrgParserState -> OrgParserState
+modifyExportSettings setter val state =
+ state { orgStateExportSettings = setter val . orgStateExportSettings $ state }
+
+--
+-- Parser state reader
+--
+
+-- | Reader monad wrapping the parser state. This is used to delay evaluation
+-- until all relevant information has been parsed and made available in the
+-- parser state. See also the newtype of the same name in
+-- Text.Pandoc.Parsing.
+newtype F a = F { unF :: Reader OrgParserState a
+ } deriving (Functor, Applicative, Monad)
+
+instance Monoid a => Monoid (F a) where
+ mempty = return mempty
+ mappend = liftM2 mappend
+ mconcat = fmap mconcat . sequence
+
+runF :: F a -> OrgParserState -> a
+runF = runReader . unF
+
+askF :: F OrgParserState
+askF = F ask
+
+asksF :: (OrgParserState -> a) -> F a
+asksF f = F $ asks f
+
+trimInlinesF :: F Inlines -> F Inlines
+trimInlinesF = liftM trimInlines
+
+returnF :: Monad m => a -> m (F a)
+returnF = return . return
diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs
index 2aaebf99f..9acfe289a 100644
--- a/src/Text/Pandoc/Writers/Docbook.hs
+++ b/src/Text/Pandoc/Writers/Docbook.hs
@@ -112,10 +112,15 @@ elementToDocbook opts lvl (Sec _ _num (id',_,_) title elements) =
else elements
tag = case lvl of
n | n == 0 -> "chapter"
- | n >= 1 && n <= 5 -> "sect" ++ show n
+ | n >= 1 && n <= 5 -> if writerDocbook5 opts
+ then "section"
+ else "sect" ++ show n
| otherwise -> "simplesect"
- in inTags True tag [("id", writerIdentifierPrefix opts ++ id') |
- not (null id')] $
+ idAttr = [("id", writerIdentifierPrefix opts ++ id') | not (null id')]
+ nsAttr = if writerDocbook5 opts && lvl == 0 then [("xmlns", "http://docbook.org/ns/docbook")]
+ else []
+ attribs = nsAttr ++ idAttr
+ in inTags True tag attribs $
inTagsSimple "title" (inlinesToDocbook opts title) $$
vcat (map (elementToDocbook opts (lvl + 1)) elements')
@@ -227,9 +232,11 @@ blockToDocbook opts (OrderedList (start, numstyle, _) (first:rest)) =
blockToDocbook opts (DefinitionList lst) =
let attribs = [("spacing", "compact") | isTightList $ concatMap snd lst]
in inTags True "variablelist" attribs $ deflistItemsToDocbook opts lst
-blockToDocbook _ (RawBlock f str)
+blockToDocbook opts (RawBlock f str)
| f == "docbook" = text str -- raw XML block
- | f == "html" = text str -- allow html for backwards compatibility
+ | f == "html" = if writerDocbook5 opts
+ then empty -- No html in Docbook5
+ else text str -- allow html for backwards compatibility
| otherwise = empty
blockToDocbook _ HorizontalRule = empty -- not semantic
blockToDocbook opts (Table caption aligns widths headers rows) =
@@ -344,7 +351,9 @@ inlineToDocbook opts (Link attr txt (src, _))
| otherwise =
(if isPrefixOf "#" src
then inTags False "link" $ ("linkend", drop 1 src) : idAndRole attr
- else inTags False "ulink" $ ("url", src) : idAndRole attr ) $
+ else if writerDocbook5 opts
+ then inTags False "link" $ ("xlink:href", src) : idAndRole attr
+ else inTags False "ulink" $ ("url", src) : idAndRole attr ) $
inlinesToDocbook opts txt
inlineToDocbook opts (Image attr _ (src, tit)) =
let titleDoc = if null tit
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 283c8bc44..9284d18ee 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -39,7 +39,8 @@ import Text.Pandoc.Templates
import Text.Printf ( printf )
import Network.URI ( isURI, unEscapeString )
import Data.Aeson (object, (.=), FromJSON)
-import Data.List ( (\\), isInfixOf, stripPrefix, intercalate, intersperse, nub, nubBy )
+import Data.List ( (\\), isInfixOf, stripPrefix, intercalate, intersperse,
+ nub, nubBy, foldl' )
import Data.Char ( toLower, isPunctuation, isAscii, isLetter, isDigit,
ord, isAlphaNum )
import Data.Maybe ( fromMaybe, isJust, catMaybes )
@@ -674,7 +675,8 @@ tableCellToLaTeX header (width, align, blocks) = do
AlignDefault -> "\\raggedright"
return $ ("\\begin{minipage}" <> valign <>
braces (text (printf "%.2f\\columnwidth" width)) <>
- (halign <> cr <> cellContents <> cr) <> "\\end{minipage}") $$
+ (halign <> "\\strut" <> cr <> cellContents <> "\\strut" <> cr) <>
+ "\\end{minipage}") $$
notesToLaTeX notes
notesToLaTeX :: [Doc] -> Doc
@@ -725,7 +727,7 @@ sectionHeader :: Bool -- True for unnumbered
-> State WriterState Doc
sectionHeader unnumbered ident level lst = do
txt <- inlineListToLaTeX lst
- plain <- stringToLaTeX TextString $ foldl (++) "" $ map stringify lst
+ plain <- stringToLaTeX TextString $ concatMap stringify lst
let noNote (Note _) = Str ""
noNote x = x
let lstNoNotes = walk noNote lst
@@ -1037,7 +1039,7 @@ citationsToNatbib (c:cs) | citationMode c == AuthorInText = do
citationsToNatbib cits = do
cits' <- mapM convertOne cits
- return $ text "\\citetext{" <> foldl combineTwo empty cits' <> text "}"
+ return $ text "\\citetext{" <> foldl' combineTwo empty cits' <> text "}"
where
combineTwo a b | isEmpty a = b
| otherwise = a <> text "; " <> b
@@ -1086,7 +1088,7 @@ citationsToBiblatex (one:[])
citationsToBiblatex (c:cs) = do
args <- mapM convertOne (c:cs)
- return $ text cmd <> foldl (<>) empty args
+ return $ text cmd <> foldl' (<>) empty args
where
cmd = case citationMode c of
AuthorInText -> "\\textcites"
@@ -1305,4 +1307,3 @@ pDocumentClass =
else do P.skipMany (P.satisfy (/='{'))
P.char '{'
P.manyTill P.letter (P.char '}')
-
diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs
index 20086ed19..e57a6fc11 100644
--- a/src/Text/Pandoc/Writers/Org.hs
+++ b/src/Text/Pandoc/Writers/Org.hs
@@ -170,7 +170,7 @@ blockToOrg (Table caption' _ _ headers rows) = do
map ((+2) . numChars) $ transpose (headers' : rawRows)
-- FIXME: Org doesn't allow blocks with height more than 1.
let hpipeBlocks blocks = hcat [beg, middle, end]
- where h = maximum (map height blocks)
+ where h = maximum (1 : map height blocks)
sep' = lblock 3 $ vcat (map text $ replicate h " | ")
beg = lblock 2 $ vcat (map text $ replicate h "| ")
end = lblock 2 $ vcat (map text $ replicate h " |")
diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs
index b292b1f11..4e0eb46a4 100644
--- a/tests/Tests/Old.hs
+++ b/tests/Tests/Old.hs
@@ -108,6 +108,9 @@ tests = [ testGroup "markdown"
, test "reader" ["-r", "docbook", "-w", "native", "-s"]
"docbook-xref.docbook" "docbook-xref.native"
]
+ , testGroup "docbook5"
+ [ testGroup "writer" $ writerTests "docbook5"
+ ]
, testGroup "native"
[ testGroup "writer" $ writerTests "native"
, test "reader" ["-r", "native", "-w", "native", "-s"]
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index bb9b37d13..fa0c57f71 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -308,6 +308,10 @@ tests =
"\\textit{Emphasised}" =?>
para (emph "Emphasised")
+ , "Inline LaTeX command with spaces" =:
+ "\\emph{Emphasis mine}" =?>
+ para (emph "Emphasis mine")
+
, "Inline LaTeX math symbol" =:
"\\tau" =?>
para (emph "τ")
@@ -328,6 +332,10 @@ tests =
"\\copy" =?>
para "©"
+ , "MathML symbols, space separated" =:
+ "\\ForAll \\Auml" =?>
+ para "∀ Ä"
+
, "LaTeX citation" =:
"\\cite{Coffee}" =?>
let citation = Citation
@@ -461,6 +469,12 @@ tests =
, "[[expl:foo][bar]]"
] =?>
(para (link "http://example.com/foo" "" "bar"))
+
+ , "Export option: Disable simple sub/superscript syntax" =:
+ unlines [ "#+OPTIONS: ^:nil"
+ , "a^b"
+ ] =?>
+ para "a^b"
]
, testGroup "Basic Blocks" $
@@ -941,7 +955,7 @@ tests =
, "Empty table" =:
"||" =?>
- simpleTable' 1 mempty mempty
+ simpleTable' 1 mempty [[mempty]]
, "Glider Table" =:
unlines [ "| 1 | 0 | 0 |"
@@ -996,6 +1010,17 @@ tests =
, [ plain "dynamic", plain "Lisp" ]
]
+ , "Table with empty cells" =:
+ "|||c|" =?>
+ simpleTable' 3 mempty [[mempty, mempty, plain "c"]]
+
+ , "Table with empty rows" =:
+ unlines [ "| first |"
+ , "| |"
+ , "| third |"
+ ] =?>
+ simpleTable' 1 mempty [[plain "first"], [mempty], [plain "third"]]
+
, "Table with alignment row" =:
unlines [ "| Numbers | Text | More |"
, "| <c> | <r> | |"
@@ -1024,10 +1049,10 @@ tests =
, "| 1 | One | foo |"
, "| 2"
] =?>
- table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0])
- [ plain "Numbers", plain "Text" , plain mempty ]
- [ [ plain "1" , plain "One" , plain "foo" ]
- , [ plain "2" , plain mempty , plain mempty ]
+ table "" (zip [AlignCenter, AlignRight] [0, 0])
+ [ plain "Numbers", plain "Text" ]
+ [ [ plain "1" , plain "One" , plain "foo" ]
+ , [ plain "2" ]
]
, "Table with caption" =:
diff --git a/tests/mediawiki-reader.native b/tests/mediawiki-reader.native
index cf80d0664..6afeb602c 100644
--- a/tests/mediawiki-reader.native
+++ b/tests/mediawiki-reader.native
@@ -252,6 +252,11 @@ Pandoc (Meta {unMeta = fromList []})
[[]]
[[[Para [Str "Orange"]]]]
,Para [Str "Paragraph",Space,Str "after",Space,Str "the",Space,Str "table."]
+,Table [] [AlignDefault,AlignDefault] [0.0,0.0]
+ [[Para [Str "fruit"]]
+ ,[Para [Str "topping"]]]
+ [[[Para [Str "apple"]]
+ ,[Para [Str "ice",Space,Str "cream"]]]]
,Header 2 ("notes",[],[]) [Str "notes"]
,Para [Str "My",Space,Str "note!",Note [Plain [Str "This."]]]
,Para [Str "URL",Space,Str "note.",Note [Plain [Link ("",[],[]) [Str "http://docs.python.org/library/functions.html#range"] ("http://docs.python.org/library/functions.html#range","")]]]]
diff --git a/tests/mediawiki-reader.wiki b/tests/mediawiki-reader.wiki
index 862bb3b48..11cd52d9c 100644
--- a/tests/mediawiki-reader.wiki
+++ b/tests/mediawiki-reader.wiki
@@ -381,6 +381,14 @@ and cheese
|Orange
|}Paragraph after the table.
+{|
+ !fruit
+ !topping
+ |-
+ |apple
+ |ice cream
+ |}
+
== notes ==
My note!<ref>This.</ref>
diff --git a/tests/tables.docbook5 b/tests/tables.docbook5
new file mode 100644
index 000000000..6224cf222
--- /dev/null
+++ b/tests/tables.docbook5
@@ -0,0 +1,432 @@
+<para>
+ Simple table with caption:
+</para>
+<table>
+ <title>
+ Demonstration of simple table syntax.
+ </title>
+ <tgroup cols="4">
+ <colspec align="right" />
+ <colspec align="left" />
+ <colspec align="center" />
+ <colspec align="left" />
+ <thead>
+ <row>
+ <entry>
+ Right
+ </entry>
+ <entry>
+ Left
+ </entry>
+ <entry>
+ Center
+ </entry>
+ <entry>
+ Default
+ </entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry>
+ 12
+ </entry>
+ <entry>
+ 12
+ </entry>
+ <entry>
+ 12
+ </entry>
+ <entry>
+ 12
+ </entry>
+ </row>
+ <row>
+ <entry>
+ 123
+ </entry>
+ <entry>
+ 123
+ </entry>
+ <entry>
+ 123
+ </entry>
+ <entry>
+ 123
+ </entry>
+ </row>
+ <row>
+ <entry>
+ 1
+ </entry>
+ <entry>
+ 1
+ </entry>
+ <entry>
+ 1
+ </entry>
+ <entry>
+ 1
+ </entry>
+ </row>
+ </tbody>
+ </tgroup>
+</table>
+<para>
+ Simple table without caption:
+</para>
+<informaltable>
+ <tgroup cols="4">
+ <colspec align="right" />
+ <colspec align="left" />
+ <colspec align="center" />
+ <colspec align="left" />
+ <thead>
+ <row>
+ <entry>
+ Right
+ </entry>
+ <entry>
+ Left
+ </entry>
+ <entry>
+ Center
+ </entry>
+ <entry>
+ Default
+ </entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry>
+ 12
+ </entry>
+ <entry>
+ 12
+ </entry>
+ <entry>
+ 12
+ </entry>
+ <entry>
+ 12
+ </entry>
+ </row>
+ <row>
+ <entry>
+ 123
+ </entry>
+ <entry>
+ 123
+ </entry>
+ <entry>
+ 123
+ </entry>
+ <entry>
+ 123
+ </entry>
+ </row>
+ <row>
+ <entry>
+ 1
+ </entry>
+ <entry>
+ 1
+ </entry>
+ <entry>
+ 1
+ </entry>
+ <entry>
+ 1
+ </entry>
+ </row>
+ </tbody>
+ </tgroup>
+</informaltable>
+<para>
+ Simple table indented two spaces:
+</para>
+<table>
+ <title>
+ Demonstration of simple table syntax.
+ </title>
+ <tgroup cols="4">
+ <colspec align="right" />
+ <colspec align="left" />
+ <colspec align="center" />
+ <colspec align="left" />
+ <thead>
+ <row>
+ <entry>
+ Right
+ </entry>
+ <entry>
+ Left
+ </entry>
+ <entry>
+ Center
+ </entry>
+ <entry>
+ Default
+ </entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry>
+ 12
+ </entry>
+ <entry>
+ 12
+ </entry>
+ <entry>
+ 12
+ </entry>
+ <entry>
+ 12
+ </entry>
+ </row>
+ <row>
+ <entry>
+ 123
+ </entry>
+ <entry>
+ 123
+ </entry>
+ <entry>
+ 123
+ </entry>
+ <entry>
+ 123
+ </entry>
+ </row>
+ <row>
+ <entry>
+ 1
+ </entry>
+ <entry>
+ 1
+ </entry>
+ <entry>
+ 1
+ </entry>
+ <entry>
+ 1
+ </entry>
+ </row>
+ </tbody>
+ </tgroup>
+</table>
+<para>
+ Multiline table with caption:
+</para>
+<table>
+ <title>
+ Here's the caption. It may span multiple lines.
+ </title>
+ <tgroup cols="4">
+ <colspec colwidth="15*" align="center" />
+ <colspec colwidth="13*" align="left" />
+ <colspec colwidth="16*" align="right" />
+ <colspec colwidth="33*" align="left" />
+ <thead>
+ <row>
+ <entry>
+ Centered Header
+ </entry>
+ <entry>
+ Left Aligned
+ </entry>
+ <entry>
+ Right Aligned
+ </entry>
+ <entry>
+ Default aligned
+ </entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry>
+ First
+ </entry>
+ <entry>
+ row
+ </entry>
+ <entry>
+ 12.0
+ </entry>
+ <entry>
+ Example of a row that spans multiple lines.
+ </entry>
+ </row>
+ <row>
+ <entry>
+ Second
+ </entry>
+ <entry>
+ row
+ </entry>
+ <entry>
+ 5.0
+ </entry>
+ <entry>
+ Here's another one. Note the blank line between rows.
+ </entry>
+ </row>
+ </tbody>
+ </tgroup>
+</table>
+<para>
+ Multiline table without caption:
+</para>
+<informaltable>
+ <tgroup cols="4">
+ <colspec colwidth="15*" align="center" />
+ <colspec colwidth="13*" align="left" />
+ <colspec colwidth="16*" align="right" />
+ <colspec colwidth="33*" align="left" />
+ <thead>
+ <row>
+ <entry>
+ Centered Header
+ </entry>
+ <entry>
+ Left Aligned
+ </entry>
+ <entry>
+ Right Aligned
+ </entry>
+ <entry>
+ Default aligned
+ </entry>
+ </row>
+ </thead>
+ <tbody>
+ <row>
+ <entry>
+ First
+ </entry>
+ <entry>
+ row
+ </entry>
+ <entry>
+ 12.0
+ </entry>
+ <entry>
+ Example of a row that spans multiple lines.
+ </entry>
+ </row>
+ <row>
+ <entry>
+ Second
+ </entry>
+ <entry>
+ row
+ </entry>
+ <entry>
+ 5.0
+ </entry>
+ <entry>
+ Here's another one. Note the blank line between rows.
+ </entry>
+ </row>
+ </tbody>
+ </tgroup>
+</informaltable>
+<para>
+ Table without column headers:
+</para>
+<informaltable>
+ <tgroup cols="4">
+ <colspec align="right" />
+ <colspec align="left" />
+ <colspec align="center" />
+ <colspec align="right" />
+ <tbody>
+ <row>
+ <entry>
+ 12
+ </entry>
+ <entry>
+ 12
+ </entry>
+ <entry>
+ 12
+ </entry>
+ <entry>
+ 12
+ </entry>
+ </row>
+ <row>
+ <entry>
+ 123
+ </entry>
+ <entry>
+ 123
+ </entry>
+ <entry>
+ 123
+ </entry>
+ <entry>
+ 123
+ </entry>
+ </row>
+ <row>
+ <entry>
+ 1
+ </entry>
+ <entry>
+ 1
+ </entry>
+ <entry>
+ 1
+ </entry>
+ <entry>
+ 1
+ </entry>
+ </row>
+ </tbody>
+ </tgroup>
+</informaltable>
+<para>
+ Multiline table without column headers:
+</para>
+<informaltable>
+ <tgroup cols="4">
+ <colspec colwidth="15*" align="center" />
+ <colspec colwidth="13*" align="left" />
+ <colspec colwidth="16*" align="right" />
+ <colspec colwidth="33*" align="left" />
+ <tbody>
+ <row>
+ <entry>
+ First
+ </entry>
+ <entry>
+ row
+ </entry>
+ <entry>
+ 12.0
+ </entry>
+ <entry>
+ Example of a row that spans multiple lines.
+ </entry>
+ </row>
+ <row>
+ <entry>
+ Second
+ </entry>
+ <entry>
+ row
+ </entry>
+ <entry>
+ 5.0
+ </entry>
+ <entry>
+ Here's another one. Note the blank line between rows.
+ </entry>
+ </row>
+ </tbody>
+ </tgroup>
+</informaltable>
diff --git a/tests/tables.latex b/tests/tables.latex
index 9f3f97e53..38d4d089e 100644
--- a/tests/tables.latex
+++ b/tests/tables.latex
@@ -52,46 +52,46 @@ Multiline table with caption:
\begin{longtable}[]{@{}clrl@{}}
\caption{Here's the caption. It may span multiple lines.}\tabularnewline
\toprule
-\begin{minipage}[b]{0.13\columnwidth}\centering
-Centered Header
-\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright
-Left Aligned
-\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft
-Right Aligned
-\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright
-Default aligned
+\begin{minipage}[b]{0.13\columnwidth}\centering\strut
+Centered Header\strut
+\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright\strut
+Left Aligned\strut
+\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft\strut
+Right Aligned\strut
+\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright\strut
+Default aligned\strut
\end{minipage}\tabularnewline
\midrule
\endfirsthead
\toprule
-\begin{minipage}[b]{0.13\columnwidth}\centering
-Centered Header
-\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright
-Left Aligned
-\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft
-Right Aligned
-\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright
-Default aligned
+\begin{minipage}[b]{0.13\columnwidth}\centering\strut
+Centered Header\strut
+\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright\strut
+Left Aligned\strut
+\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft\strut
+Right Aligned\strut
+\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright\strut
+Default aligned\strut
\end{minipage}\tabularnewline
\midrule
\endhead
-\begin{minipage}[t]{0.13\columnwidth}\centering
-First
-\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright
-row
-\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft
-12.0
-\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright
-Example of a row that spans multiple lines.
+\begin{minipage}[t]{0.13\columnwidth}\centering\strut
+First\strut
+\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright\strut
+row\strut
+\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft\strut
+12.0\strut
+\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright\strut
+Example of a row that spans multiple lines.\strut
\end{minipage}\tabularnewline
-\begin{minipage}[t]{0.13\columnwidth}\centering
-Second
-\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright
-row
-\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft
-5.0
-\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright
-Here's another one. Note the blank line between rows.
+\begin{minipage}[t]{0.13\columnwidth}\centering\strut
+Second\strut
+\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright\strut
+row\strut
+\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft\strut
+5.0\strut
+\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright\strut
+Here's another one. Note the blank line between rows.\strut
\end{minipage}\tabularnewline
\bottomrule
\end{longtable}
@@ -100,34 +100,34 @@ Multiline table without caption:
\begin{longtable}[]{@{}clrl@{}}
\toprule
-\begin{minipage}[b]{0.13\columnwidth}\centering
-Centered Header
-\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright
-Left Aligned
-\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft
-Right Aligned
-\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright
-Default aligned
+\begin{minipage}[b]{0.13\columnwidth}\centering\strut
+Centered Header\strut
+\end{minipage} & \begin{minipage}[b]{0.12\columnwidth}\raggedright\strut
+Left Aligned\strut
+\end{minipage} & \begin{minipage}[b]{0.14\columnwidth}\raggedleft\strut
+Right Aligned\strut
+\end{minipage} & \begin{minipage}[b]{0.30\columnwidth}\raggedright\strut
+Default aligned\strut
\end{minipage}\tabularnewline
\midrule
\endhead
-\begin{minipage}[t]{0.13\columnwidth}\centering
-First
-\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright
-row
-\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft
-12.0
-\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright
-Example of a row that spans multiple lines.
+\begin{minipage}[t]{0.13\columnwidth}\centering\strut
+First\strut
+\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright\strut
+row\strut
+\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft\strut
+12.0\strut
+\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright\strut
+Example of a row that spans multiple lines.\strut
\end{minipage}\tabularnewline
-\begin{minipage}[t]{0.13\columnwidth}\centering
-Second
-\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright
-row
-\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft
-5.0
-\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright
-Here's another one. Note the blank line between rows.
+\begin{minipage}[t]{0.13\columnwidth}\centering\strut
+Second\strut
+\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright\strut
+row\strut
+\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft\strut
+5.0\strut
+\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright\strut
+Here's another one. Note the blank line between rows.\strut
\end{minipage}\tabularnewline
\bottomrule
\end{longtable}
@@ -146,23 +146,23 @@ Multiline table without column headers:
\begin{longtable}[]{@{}clrl@{}}
\toprule
-\begin{minipage}[t]{0.13\columnwidth}\centering
-First
-\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright
-row
-\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft
-12.0
-\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright
-Example of a row that spans multiple lines.
+\begin{minipage}[t]{0.13\columnwidth}\centering\strut
+First\strut
+\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright\strut
+row\strut
+\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft\strut
+12.0\strut
+\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright\strut
+Example of a row that spans multiple lines.\strut
\end{minipage}\tabularnewline
-\begin{minipage}[t]{0.13\columnwidth}\centering
-Second
-\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright
-row
-\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft
-5.0
-\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright
-Here's another one. Note the blank line between rows.
+\begin{minipage}[t]{0.13\columnwidth}\centering\strut
+Second\strut
+\end{minipage} & \begin{minipage}[t]{0.12\columnwidth}\raggedright\strut
+row\strut
+\end{minipage} & \begin{minipage}[t]{0.14\columnwidth}\raggedleft\strut
+5.0\strut
+\end{minipage} & \begin{minipage}[t]{0.30\columnwidth}\raggedright\strut
+Here's another one. Note the blank line between rows.\strut
\end{minipage}\tabularnewline
\bottomrule
\end{longtable}
diff --git a/tests/writer.docbook5 b/tests/writer.docbook5
new file mode 100644
index 000000000..5261a35be
--- /dev/null
+++ b/tests/writer.docbook5
@@ -0,0 +1,1395 @@
+<?xml version="1.0" encoding="utf-8" ?>
+<!DOCTYPE article>
+<article xmlns="http://docbook.org/ns/docbook" version="5.0">
+ <info>
+ <title>Pandoc Test Suite</title>
+ <authorgroup>
+ <author>
+ <firstname>John</firstname>
+ <surname>MacFarlane</surname>
+ </author>
+ <author>
+ <firstname></firstname>
+ <surname>Anonymous</surname>
+ </author>
+ </authorgroup>
+ <date>July 17, 2006</date>
+ </info>
+<para>
+ This is a set of tests for pandoc. Most of them are adapted from John
+ Gruber’s markdown test suite.
+</para>
+<section id="headers">
+ <title>Headers</title>
+ <section id="level-2-with-an-embedded-link">
+ <title>Level 2 with an <link xlink:href="/url">embedded
+ link</link></title>
+ <section id="level-3-with-emphasis">
+ <title>Level 3 with <emphasis>emphasis</emphasis></title>
+ <section id="level-4">
+ <title>Level 4</title>
+ <section id="level-5">
+ <title>Level 5</title>
+ <para>
+ </para>
+ </section>
+ </section>
+ </section>
+ </section>
+</section>
+<section id="level-1">
+ <title>Level 1</title>
+ <section id="level-2-with-emphasis">
+ <title>Level 2 with <emphasis>emphasis</emphasis></title>
+ <section id="level-3">
+ <title>Level 3</title>
+ <para>
+ with no blank line
+ </para>
+ </section>
+ </section>
+ <section id="level-2">
+ <title>Level 2</title>
+ <para>
+ with no blank line
+ </para>
+ </section>
+</section>
+<section id="paragraphs">
+ <title>Paragraphs</title>
+ <para>
+ Here’s a regular paragraph.
+ </para>
+ <para>
+ In Markdown 1.0.0 and earlier. Version 8. This line turns into a list
+ item. Because a hard-wrapped line in the middle of a paragraph looked like
+ a list item.
+ </para>
+ <para>
+ Here’s one with a bullet. * criminey.
+ </para>
+<literallayout>There should be a hard line break
+here.</literallayout>
+</section>
+<section id="block-quotes">
+ <title>Block Quotes</title>
+ <para>
+ E-mail style:
+ </para>
+ <blockquote>
+ <para>
+ This is a block quote. It is pretty short.
+ </para>
+ </blockquote>
+ <blockquote>
+ <para>
+ Code in a block quote:
+ </para>
+ <programlisting>
+sub status {
+ print &quot;working&quot;;
+}
+</programlisting>
+ <para>
+ A list:
+ </para>
+ <orderedlist numeration="arabic" spacing="compact">
+ <listitem>
+ <para>
+ item one
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ item two
+ </para>
+ </listitem>
+ </orderedlist>
+ <para>
+ Nested block quotes:
+ </para>
+ <blockquote>
+ <para>
+ nested
+ </para>
+ </blockquote>
+ <blockquote>
+ <para>
+ nested
+ </para>
+ </blockquote>
+ </blockquote>
+ <para>
+ This should not be a block quote: 2 &gt; 1.
+ </para>
+ <para>
+ And a following paragraph.
+ </para>
+</section>
+<section id="code-blocks">
+ <title>Code Blocks</title>
+ <para>
+ Code:
+ </para>
+ <programlisting>
+---- (should be four hyphens)
+
+sub status {
+ print &quot;working&quot;;
+}
+
+this code block is indented by one tab
+</programlisting>
+ <para>
+ And:
+ </para>
+ <programlisting>
+ this code block is indented by two tabs
+
+These should not be escaped: \$ \\ \&gt; \[ \{
+</programlisting>
+</section>
+<section id="lists">
+ <title>Lists</title>
+ <section id="unordered">
+ <title>Unordered</title>
+ <para>
+ Asterisks tight:
+ </para>
+ <itemizedlist spacing="compact">
+ <listitem>
+ <para>
+ asterisk 1
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ asterisk 2
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ asterisk 3
+ </para>
+ </listitem>
+ </itemizedlist>
+ <para>
+ Asterisks loose:
+ </para>
+ <itemizedlist>
+ <listitem>
+ <para>
+ asterisk 1
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ asterisk 2
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ asterisk 3
+ </para>
+ </listitem>
+ </itemizedlist>
+ <para>
+ Pluses tight:
+ </para>
+ <itemizedlist spacing="compact">
+ <listitem>
+ <para>
+ Plus 1
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Plus 2
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Plus 3
+ </para>
+ </listitem>
+ </itemizedlist>
+ <para>
+ Pluses loose:
+ </para>
+ <itemizedlist>
+ <listitem>
+ <para>
+ Plus 1
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Plus 2
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Plus 3
+ </para>
+ </listitem>
+ </itemizedlist>
+ <para>
+ Minuses tight:
+ </para>
+ <itemizedlist spacing="compact">
+ <listitem>
+ <para>
+ Minus 1
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Minus 2
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Minus 3
+ </para>
+ </listitem>
+ </itemizedlist>
+ <para>
+ Minuses loose:
+ </para>
+ <itemizedlist>
+ <listitem>
+ <para>
+ Minus 1
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Minus 2
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Minus 3
+ </para>
+ </listitem>
+ </itemizedlist>
+ </section>
+ <section id="ordered">
+ <title>Ordered</title>
+ <para>
+ Tight:
+ </para>
+ <orderedlist numeration="arabic" spacing="compact">
+ <listitem>
+ <para>
+ First
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Second
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Third
+ </para>
+ </listitem>
+ </orderedlist>
+ <para>
+ and:
+ </para>
+ <orderedlist numeration="arabic" spacing="compact">
+ <listitem>
+ <para>
+ One
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Two
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Three
+ </para>
+ </listitem>
+ </orderedlist>
+ <para>
+ Loose using tabs:
+ </para>
+ <orderedlist numeration="arabic">
+ <listitem>
+ <para>
+ First
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Second
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Third
+ </para>
+ </listitem>
+ </orderedlist>
+ <para>
+ and using spaces:
+ </para>
+ <orderedlist numeration="arabic">
+ <listitem>
+ <para>
+ One
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Two
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Three
+ </para>
+ </listitem>
+ </orderedlist>
+ <para>
+ Multiple paragraphs:
+ </para>
+ <orderedlist numeration="arabic">
+ <listitem>
+ <para>
+ Item 1, graf one.
+ </para>
+ <para>
+ Item 1. graf two. The quick brown fox jumped over the lazy dog’s
+ back.
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Item 2.
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Item 3.
+ </para>
+ </listitem>
+ </orderedlist>
+ </section>
+ <section id="nested">
+ <title>Nested</title>
+ <itemizedlist spacing="compact">
+ <listitem>
+ <para>
+ Tab
+ </para>
+ <itemizedlist spacing="compact">
+ <listitem>
+ <para>
+ Tab
+ </para>
+ <itemizedlist spacing="compact">
+ <listitem>
+ <para>
+ Tab
+ </para>
+ </listitem>
+ </itemizedlist>
+ </listitem>
+ </itemizedlist>
+ </listitem>
+ </itemizedlist>
+ <para>
+ Here’s another:
+ </para>
+ <orderedlist numeration="arabic" spacing="compact">
+ <listitem>
+ <para>
+ First
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Second:
+ </para>
+ <itemizedlist spacing="compact">
+ <listitem>
+ <para>
+ Fee
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Fie
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Foe
+ </para>
+ </listitem>
+ </itemizedlist>
+ </listitem>
+ <listitem>
+ <para>
+ Third
+ </para>
+ </listitem>
+ </orderedlist>
+ <para>
+ Same thing but with paragraphs:
+ </para>
+ <orderedlist numeration="arabic">
+ <listitem>
+ <para>
+ First
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Second:
+ </para>
+ <itemizedlist spacing="compact">
+ <listitem>
+ <para>
+ Fee
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Fie
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Foe
+ </para>
+ </listitem>
+ </itemizedlist>
+ </listitem>
+ <listitem>
+ <para>
+ Third
+ </para>
+ </listitem>
+ </orderedlist>
+ </section>
+ <section id="tabs-and-spaces">
+ <title>Tabs and spaces</title>
+ <itemizedlist>
+ <listitem>
+ <para>
+ this is a list item indented with tabs
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ this is a list item indented with spaces
+ </para>
+ <itemizedlist>
+ <listitem>
+ <para>
+ this is an example list item indented with tabs
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ this is an example list item indented with spaces
+ </para>
+ </listitem>
+ </itemizedlist>
+ </listitem>
+ </itemizedlist>
+ </section>
+ <section id="fancy-list-markers">
+ <title>Fancy list markers</title>
+ <orderedlist numeration="arabic">
+ <listitem override="2">
+ <para>
+ begins with 2
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ and now 3
+ </para>
+ <para>
+ with a continuation
+ </para>
+ <orderedlist numeration="lowerroman" spacing="compact">
+ <listitem override="4">
+ <para>
+ sublist with roman numerals, starting with 4
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ more items
+ </para>
+ <orderedlist numeration="upperalpha" spacing="compact">
+ <listitem>
+ <para>
+ a subsublist
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ a subsublist
+ </para>
+ </listitem>
+ </orderedlist>
+ </listitem>
+ </orderedlist>
+ </listitem>
+ </orderedlist>
+ <para>
+ Nesting:
+ </para>
+ <orderedlist numeration="upperalpha" spacing="compact">
+ <listitem>
+ <para>
+ Upper Alpha
+ </para>
+ <orderedlist numeration="upperroman" spacing="compact">
+ <listitem>
+ <para>
+ Upper Roman.
+ </para>
+ <orderedlist numeration="arabic" spacing="compact">
+ <listitem override="6">
+ <para>
+ Decimal start with 6
+ </para>
+ <orderedlist numeration="loweralpha" spacing="compact">
+ <listitem override="3">
+ <para>
+ Lower alpha with paren
+ </para>
+ </listitem>
+ </orderedlist>
+ </listitem>
+ </orderedlist>
+ </listitem>
+ </orderedlist>
+ </listitem>
+ </orderedlist>
+ <para>
+ Autonumbering:
+ </para>
+ <orderedlist spacing="compact">
+ <listitem>
+ <para>
+ Autonumber.
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ More.
+ </para>
+ <orderedlist spacing="compact">
+ <listitem>
+ <para>
+ Nested.
+ </para>
+ </listitem>
+ </orderedlist>
+ </listitem>
+ </orderedlist>
+ <para>
+ Should not be a list item:
+ </para>
+ <para>
+ M.A. 2007
+ </para>
+ <para>
+ B. Williams
+ </para>
+ </section>
+</section>
+<section id="definition-lists">
+ <title>Definition Lists</title>
+ <para>
+ Tight using spaces:
+ </para>
+ <variablelist spacing="compact">
+ <varlistentry>
+ <term>
+ apple
+ </term>
+ <listitem>
+ <para>
+ red fruit
+ </para>
+ </listitem>
+ </varlistentry>
+ <varlistentry>
+ <term>
+ orange
+ </term>
+ <listitem>
+ <para>
+ orange fruit
+ </para>
+ </listitem>
+ </varlistentry>
+ <varlistentry>
+ <term>
+ banana
+ </term>
+ <listitem>
+ <para>
+ yellow fruit
+ </para>
+ </listitem>
+ </varlistentry>
+ </variablelist>
+ <para>
+ Tight using tabs:
+ </para>
+ <variablelist spacing="compact">
+ <varlistentry>
+ <term>
+ apple
+ </term>
+ <listitem>
+ <para>
+ red fruit
+ </para>
+ </listitem>
+ </varlistentry>
+ <varlistentry>
+ <term>
+ orange
+ </term>
+ <listitem>
+ <para>
+ orange fruit
+ </para>
+ </listitem>
+ </varlistentry>
+ <varlistentry>
+ <term>
+ banana
+ </term>
+ <listitem>
+ <para>
+ yellow fruit
+ </para>
+ </listitem>
+ </varlistentry>
+ </variablelist>
+ <para>
+ Loose:
+ </para>
+ <variablelist>
+ <varlistentry>
+ <term>
+ apple
+ </term>
+ <listitem>
+ <para>
+ red fruit
+ </para>
+ </listitem>
+ </varlistentry>
+ <varlistentry>
+ <term>
+ orange
+ </term>
+ <listitem>
+ <para>
+ orange fruit
+ </para>
+ </listitem>
+ </varlistentry>
+ <varlistentry>
+ <term>
+ banana
+ </term>
+ <listitem>
+ <para>
+ yellow fruit
+ </para>
+ </listitem>
+ </varlistentry>
+ </variablelist>
+ <para>
+ Multiple blocks with italics:
+ </para>
+ <variablelist>
+ <varlistentry>
+ <term>
+ <emphasis>apple</emphasis>
+ </term>
+ <listitem>
+ <para>
+ red fruit
+ </para>
+ <para>
+ contains seeds, crisp, pleasant to taste
+ </para>
+ </listitem>
+ </varlistentry>
+ <varlistentry>
+ <term>
+ <emphasis>orange</emphasis>
+ </term>
+ <listitem>
+ <para>
+ orange fruit
+ </para>
+ <programlisting>
+{ orange code block }
+</programlisting>
+ <blockquote>
+ <para>
+ orange block quote
+ </para>
+ </blockquote>
+ </listitem>
+ </varlistentry>
+ </variablelist>
+ <para>
+ Multiple definitions, tight:
+ </para>
+ <variablelist spacing="compact">
+ <varlistentry>
+ <term>
+ apple
+ </term>
+ <listitem>
+ <para>
+ red fruit
+ </para>
+ <para>
+ computer
+ </para>
+ </listitem>
+ </varlistentry>
+ <varlistentry>
+ <term>
+ orange
+ </term>
+ <listitem>
+ <para>
+ orange fruit
+ </para>
+ <para>
+ bank
+ </para>
+ </listitem>
+ </varlistentry>
+ </variablelist>
+ <para>
+ Multiple definitions, loose:
+ </para>
+ <variablelist>
+ <varlistentry>
+ <term>
+ apple
+ </term>
+ <listitem>
+ <para>
+ red fruit
+ </para>
+ <para>
+ computer
+ </para>
+ </listitem>
+ </varlistentry>
+ <varlistentry>
+ <term>
+ orange
+ </term>
+ <listitem>
+ <para>
+ orange fruit
+ </para>
+ <para>
+ bank
+ </para>
+ </listitem>
+ </varlistentry>
+ </variablelist>
+ <para>
+ Blank line after term, indented marker, alternate markers:
+ </para>
+ <variablelist>
+ <varlistentry>
+ <term>
+ apple
+ </term>
+ <listitem>
+ <para>
+ red fruit
+ </para>
+ <para>
+ computer
+ </para>
+ </listitem>
+ </varlistentry>
+ <varlistentry>
+ <term>
+ orange
+ </term>
+ <listitem>
+ <para>
+ orange fruit
+ </para>
+ <orderedlist numeration="arabic" spacing="compact">
+ <listitem>
+ <para>
+ sublist
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ sublist
+ </para>
+ </listitem>
+ </orderedlist>
+ </listitem>
+ </varlistentry>
+ </variablelist>
+</section>
+<section id="html-blocks">
+ <title>HTML Blocks</title>
+ <para>
+ Simple block on one line:
+ </para>
+ <para>
+ foo
+ </para>
+ <para>
+ And nested without indentation:
+ </para>
+ <para>
+ foo
+ </para>
+ <para>
+ bar
+ </para>
+ <para>
+ Interpreted markdown in a table:
+ </para>
+ This is <emphasis>emphasized</emphasis>
+ And this is <emphasis role="strong">strong</emphasis>
+ <para>
+ Here’s a simple block:
+ </para>
+ <para>
+ foo
+ </para>
+ <para>
+ This should be a code block, though:
+ </para>
+ <programlisting>
+&lt;div&gt;
+ foo
+&lt;/div&gt;
+</programlisting>
+ <para>
+ As should this:
+ </para>
+ <programlisting>
+&lt;div&gt;foo&lt;/div&gt;
+</programlisting>
+ <para>
+ Now, nested:
+ </para>
+ <para>
+ foo
+ </para>
+ <para>
+ This should just be an HTML comment:
+ </para>
+ <para>
+ Multiline:
+ </para>
+ <para>
+ Code block:
+ </para>
+ <programlisting>
+&lt;!-- Comment --&gt;
+</programlisting>
+ <para>
+ Just plain comment, with trailing spaces on the line:
+ </para>
+ <para>
+ Code:
+ </para>
+ <programlisting>
+&lt;hr /&gt;
+</programlisting>
+ <para>
+ Hr’s:
+ </para>
+</section>
+<section id="inline-markup">
+ <title>Inline Markup</title>
+ <para>
+ This is <emphasis>emphasized</emphasis>, and so <emphasis>is
+ this</emphasis>.
+ </para>
+ <para>
+ This is <emphasis role="strong">strong</emphasis>, and so
+ <emphasis role="strong">is this</emphasis>.
+ </para>
+ <para>
+ An <emphasis><link xlink:href="/url">emphasized link</link></emphasis>.
+ </para>
+ <para>
+ <emphasis role="strong"><emphasis>This is strong and
+ em.</emphasis></emphasis>
+ </para>
+ <para>
+ So is <emphasis role="strong"><emphasis>this</emphasis></emphasis> word.
+ </para>
+ <para>
+ <emphasis role="strong"><emphasis>This is strong and
+ em.</emphasis></emphasis>
+ </para>
+ <para>
+ So is <emphasis role="strong"><emphasis>this</emphasis></emphasis> word.
+ </para>
+ <para>
+ This is code: <literal>&gt;</literal>, <literal>$</literal>,
+ <literal>\</literal>, <literal>\$</literal>,
+ <literal>&lt;html&gt;</literal>.
+ </para>
+ <para>
+ <emphasis role="strikethrough">This is
+ <emphasis>strikeout</emphasis>.</emphasis>
+ </para>
+ <para>
+ Superscripts: a<superscript>bc</superscript>d
+ a<superscript><emphasis>hello</emphasis></superscript>
+ a<superscript>hello there</superscript>.
+ </para>
+ <para>
+ Subscripts: H<subscript>2</subscript>O, H<subscript>23</subscript>O,
+ H<subscript>many of them</subscript>O.
+ </para>
+ <para>
+ These should not be superscripts or subscripts, because of the unescaped
+ spaces: a^b c^d, a~b c~d.
+ </para>
+</section>
+<section id="smart-quotes-ellipses-dashes">
+ <title>Smart quotes, ellipses, dashes</title>
+ <para>
+ <quote>Hello,</quote> said the spider. <quote><quote>Shelob</quote> is my
+ name.</quote>
+ </para>
+ <para>
+ <quote>A</quote>, <quote>B</quote>, and <quote>C</quote> are letters.
+ </para>
+ <para>
+ <quote>Oak,</quote> <quote>elm,</quote> and <quote>beech</quote> are names
+ of trees. So is <quote>pine.</quote>
+ </para>
+ <para>
+ <quote>He said, <quote>I want to go.</quote></quote> Were you alive in the
+ 70’s?
+ </para>
+ <para>
+ Here is some quoted <quote><literal>code</literal></quote> and a
+ <quote><link xlink:href="http://example.com/?foo=1&amp;bar=2">quoted
+ link</link></quote>.
+ </para>
+ <para>
+ Some dashes: one—two — three—four — five.
+ </para>
+ <para>
+ Dashes between numbers: 5–7, 255–66, 1987–1999.
+ </para>
+ <para>
+ Ellipses…and…and….
+ </para>
+</section>
+<section id="latex">
+ <title>LaTeX</title>
+ <itemizedlist spacing="compact">
+ <listitem>
+ <para>
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ 2 + 2 = 4
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ <emphasis>x</emphasis> ∈ <emphasis>y</emphasis>
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ <emphasis>α</emphasis> ∧ <emphasis>ω</emphasis>
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ 223
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ <emphasis>p</emphasis>-Tree
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Here’s some display math:
+ $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Here’s one that has a line break in it:
+ <emphasis>α</emphasis> + <emphasis>ω</emphasis> × <emphasis>x</emphasis><superscript>2</superscript>.
+ </para>
+ </listitem>
+ </itemizedlist>
+ <para>
+ These shouldn’t be math:
+ </para>
+ <itemizedlist spacing="compact">
+ <listitem>
+ <para>
+ To get the famous equation, write <literal>$e = mc^2$</literal>.
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ $22,000 is a <emphasis>lot</emphasis> of money. So is $34,000. (It
+ worked if <quote>lot</quote> is emphasized.)
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Shoes ($20) and socks ($5).
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ Escaped <literal>$</literal>: $73 <emphasis>this should be
+ emphasized</emphasis> 23$.
+ </para>
+ </listitem>
+ </itemizedlist>
+ <para>
+ Here’s a LaTeX table:
+ </para>
+</section>
+<section id="special-characters">
+ <title>Special Characters</title>
+ <para>
+ Here is some unicode:
+ </para>
+ <itemizedlist spacing="compact">
+ <listitem>
+ <para>
+ I hat: Î
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ o umlaut: ö
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ section: §
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ set membership: ∈
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ copyright: ©
+ </para>
+ </listitem>
+ </itemizedlist>
+ <para>
+ AT&amp;T has an ampersand in their name.
+ </para>
+ <para>
+ AT&amp;T is another way to write it.
+ </para>
+ <para>
+ This &amp; that.
+ </para>
+ <para>
+ 4 &lt; 5.
+ </para>
+ <para>
+ 6 &gt; 5.
+ </para>
+ <para>
+ Backslash: \
+ </para>
+ <para>
+ Backtick: `
+ </para>
+ <para>
+ Asterisk: *
+ </para>
+ <para>
+ Underscore: _
+ </para>
+ <para>
+ Left brace: {
+ </para>
+ <para>
+ Right brace: }
+ </para>
+ <para>
+ Left bracket: [
+ </para>
+ <para>
+ Right bracket: ]
+ </para>
+ <para>
+ Left paren: (
+ </para>
+ <para>
+ Right paren: )
+ </para>
+ <para>
+ Greater-than: &gt;
+ </para>
+ <para>
+ Hash: #
+ </para>
+ <para>
+ Period: .
+ </para>
+ <para>
+ Bang: !
+ </para>
+ <para>
+ Plus: +
+ </para>
+ <para>
+ Minus: -
+ </para>
+</section>
+<section id="links">
+ <title>Links</title>
+ <section id="explicit">
+ <title>Explicit</title>
+ <para>
+ Just a <link xlink:href="/url/">URL</link>.
+ </para>
+ <para>
+ <link xlink:href="/url/">URL and title</link>.
+ </para>
+ <para>
+ <link xlink:href="/url/">URL and title</link>.
+ </para>
+ <para>
+ <link xlink:href="/url/">URL and title</link>.
+ </para>
+ <para>
+ <link xlink:href="/url/">URL and title</link>
+ </para>
+ <para>
+ <link xlink:href="/url/">URL and title</link>
+ </para>
+ <para>
+ <link xlink:href="/url/with_underscore">with_underscore</link>
+ </para>
+ <para>
+ Email link (<email>nobody@nowhere.net</email>)
+ </para>
+ <para>
+ <link xlink:href="">Empty</link>.
+ </para>
+ </section>
+ <section id="reference">
+ <title>Reference</title>
+ <para>
+ Foo <link xlink:href="/url/">bar</link>.
+ </para>
+ <para>
+ Foo <link xlink:href="/url/">bar</link>.
+ </para>
+ <para>
+ Foo <link xlink:href="/url/">bar</link>.
+ </para>
+ <para>
+ With <link xlink:href="/url/">embedded [brackets]</link>.
+ </para>
+ <para>
+ <link xlink:href="/url/">b</link> by itself should be a link.
+ </para>
+ <para>
+ Indented <link xlink:href="/url">once</link>.
+ </para>
+ <para>
+ Indented <link xlink:href="/url">twice</link>.
+ </para>
+ <para>
+ Indented <link xlink:href="/url">thrice</link>.
+ </para>
+ <para>
+ This should [not][] be a link.
+ </para>
+ <programlisting>
+[not]: /url
+</programlisting>
+ <para>
+ Foo <link xlink:href="/url/">bar</link>.
+ </para>
+ <para>
+ Foo <link xlink:href="/url/">biz</link>.
+ </para>
+ </section>
+ <section id="with-ampersands">
+ <title>With ampersands</title>
+ <para>
+ Here’s a <link xlink:href="http://example.com/?foo=1&amp;bar=2">link
+ with an ampersand in the URL</link>.
+ </para>
+ <para>
+ Here’s a link with an amersand in the link text:
+ <link xlink:href="http://att.com/">AT&amp;T</link>.
+ </para>
+ <para>
+ Here’s an <link xlink:href="/script?foo=1&amp;bar=2">inline link</link>.
+ </para>
+ <para>
+ Here’s an <link xlink:href="/script?foo=1&amp;bar=2">inline link in
+ pointy braces</link>.
+ </para>
+ </section>
+ <section id="autolinks">
+ <title>Autolinks</title>
+ <para>
+ With an ampersand:
+ <link xlink:href="http://example.com/?foo=1&amp;bar=2">http://example.com/?foo=1&amp;bar=2</link>
+ </para>
+ <itemizedlist spacing="compact">
+ <listitem>
+ <para>
+ In a list?
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ <link xlink:href="http://example.com/">http://example.com/</link>
+ </para>
+ </listitem>
+ <listitem>
+ <para>
+ It should.
+ </para>
+ </listitem>
+ </itemizedlist>
+ <para>
+ An e-mail address: <email>nobody@nowhere.net</email>
+ </para>
+ <blockquote>
+ <para>
+ Blockquoted:
+ <link xlink:href="http://example.com/">http://example.com/</link>
+ </para>
+ </blockquote>
+ <para>
+ Auto-links should not occur here:
+ <literal>&lt;http://example.com/&gt;</literal>
+ </para>
+ <programlisting>
+or here: &lt;http://example.com/&gt;
+</programlisting>
+ </section>
+</section>
+<section id="images">
+ <title>Images</title>
+ <para>
+ From <quote>Voyage dans la Lune</quote> by Georges Melies (1902):
+ </para>
+ <figure>
+ <title>lalune</title>
+ <mediaobject>
+ <imageobject>
+ <imagedata fileref="lalune.jpg" />
+ </imageobject>
+ <textobject><phrase>lalune</phrase></textobject>
+ </mediaobject>
+ </figure>
+ <para>
+ Here is a movie <inlinemediaobject>
+ <imageobject>
+ <imagedata fileref="movie.jpg" />
+ </imageobject>
+ </inlinemediaobject> icon.
+ </para>
+</section>
+<section id="footnotes">
+ <title>Footnotes</title>
+ <para>
+ Here is a footnote reference,<footnote>
+ <para>
+ Here is the footnote. It can go anywhere after the footnote reference.
+ It need not be placed at the end of the document.
+ </para>
+ </footnote> and another.<footnote>
+ <para>
+ Here’s the long note. This one contains multiple blocks.
+ </para>
+ <para>
+ Subsequent blocks are indented to show that they belong to the
+ footnote (as with list items).
+ </para>
+ <programlisting>
+ { &lt;code&gt; }
+</programlisting>
+ <para>
+ If you want, you can indent every line, but you can also be lazy and
+ just indent the first line of each block.
+ </para>
+ </footnote> This should <emphasis>not</emphasis> be a footnote reference,
+ because it contains a space.[^my note] Here is an inline note.<footnote>
+ <para>
+ This is <emphasis>easier</emphasis> to type. Inline notes may contain
+ <link xlink:href="http://google.com">links</link> and
+ <literal>]</literal> verbatim characters, as well as [bracketed text].
+ </para>
+ </footnote>
+ </para>
+ <blockquote>
+ <para>
+ Notes can go in quotes.<footnote>
+ <para>
+ In quote.
+ </para>
+ </footnote>
+ </para>
+ </blockquote>
+ <orderedlist numeration="arabic" spacing="compact">
+ <listitem>
+ <para>
+ And in list items.<footnote>
+ <para>
+ In list.
+ </para>
+ </footnote>
+ </para>
+ </listitem>
+ </orderedlist>
+ <para>
+ This paragraph should not be part of the note, as it is not indented.
+ </para>
+</section>
+</article>
diff --git a/windows/stack-appveyor.yaml b/windows/stack-appveyor.yaml
new file mode 100644
index 000000000..e5a2b138e
--- /dev/null
+++ b/windows/stack-appveyor.yaml
@@ -0,0 +1,20 @@
+flags:
+ pandoc:
+ trypandoc: false
+ https: true
+ embed_data_files: true
+ old-locale: false
+ network-uri: true
+packages:
+- '..'
+extra-deps:
+- 'hsb2hs-0.3.1'
+- 'texmath-0.8.6.2'
+- 'data-default-0.6.0'
+- 'data-default-instances-base-0.1.0'
+- 'preprocessor-tools-1.0.1'
+# to compile against aeson 0.11.0.0:
+# - 'aeson-0.11.0.0'
+# - 'fail-4.9.0.0'
+# - 'pandoc-types-1.16.1'
+resolver: lts-5.8