diff options
-rw-r--r-- | README | 9 | ||||
-rw-r--r-- | pandoc.cabal | 4 | ||||
-rw-r--r-- | pandoc.hs | 26 | ||||
-rw-r--r-- | src/Text/Pandoc/Options.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/PDF.hs | 16 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 32 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Markdown.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/MediaWiki.hs | 10 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org.hs | 58 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/HTML.hs | 11 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Markdown.hs | 7 | ||||
-rw-r--r-- | tests/Tests/Readers/LaTeX.hs | 39 | ||||
-rw-r--r-- | tests/Tests/Readers/Org.hs | 24 | ||||
-rw-r--r-- | tests/pipe-tables.txt | 4 |
14 files changed, 197 insertions, 53 deletions
@@ -655,6 +655,11 @@ Options affecting specific writers The default is `pdflatex`. If the engine is not in your PATH, the full path of the engine may be specified here. +`--latex-engine-opt=`*STRING* +: Use the given string as a command-line argument to the `latex-engine`. + If used multiple times, the arguments are provided with spaces between + them. Note that no check for duplicate options is done. + Citation rendering ------------------ @@ -1822,8 +1827,8 @@ Pipe tables look like this: The syntax is [the same as in PHP markdown extra]. The beginning and ending pipe characters are optional, but pipes are required between all columns. The colons indicate column alignment as shown. The header -can be omitted, but the horizontal line must still be included, as -it defines column alignments. +cannot be omitted. To simulate a headerless table, include a header +with blank cells. Since the pipes indicate column boundaries, columns need not be vertically aligned, as they are in the above example. So, this is a perfectly diff --git a/pandoc.cabal b/pandoc.cabal index 16106f896..a80696c99 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -242,8 +242,8 @@ Library highlighting-kate >= 0.5.11.1 && < 0.6, data-default >= 0.4 && < 0.6, temporary >= 1.1 && < 1.3, - blaze-html >= 0.5 && < 0.8, - blaze-markup >= 0.5.1 && < 0.7, + blaze-html >= 0.5 && < 0.9, + blaze-markup >= 0.5.1 && < 0.8, yaml >= 0.8.8.2 && < 0.9, scientific >= 0.2 && < 0.4, vector >= 0.10 && < 0.11, @@ -49,7 +49,7 @@ import System.Exit ( exitWith, ExitCode (..) ) import System.FilePath import System.Console.GetOpt import Data.Char ( toLower ) -import Data.List ( intercalate, isPrefixOf, isSuffixOf, sort ) +import Data.List ( delete, intercalate, isPrefixOf, isSuffixOf, sort ) import System.Directory ( getAppUserDataDirectory, findExecutable, doesFileExist, Permissions(..), getPermissions ) import System.IO ( stdout, stderr ) @@ -198,6 +198,7 @@ data Opt = Opt , optCiteMethod :: CiteMethod -- ^ Method to output cites , optListings :: Bool -- ^ Use listings package for code blocks , optLaTeXEngine :: String -- ^ Program to use for latex -> pdf + , optLaTeXEngineArgs :: [String] -- ^ Flags to pass to the latex-engine , optSlideLevel :: Maybe Int -- ^ Header level that creates slides , optSetextHeaders :: Bool -- ^ Use atx headers for markdown level 1-2 , optAscii :: Bool -- ^ Use ascii characters only in html @@ -259,6 +260,7 @@ defaultOpts = Opt , optCiteMethod = Citeproc , optListings = False , optLaTeXEngine = "pdflatex" + , optLaTeXEngineArgs = [] , optSlideLevel = Nothing , optSetextHeaders = True , optAscii = False @@ -734,6 +736,14 @@ options = "PROGRAM") "" -- "Name of latex program to use in generating PDF" + , Option "" ["latex-engine-opt"] + (ReqArg + (\arg opt -> do + let oldArgs = optLaTeXEngineArgs opt + return opt { optLaTeXEngineArgs = arg : oldArgs }) + "STRING") + "" -- "Flags to pass to the LaTeX engine, all instances of this option are accumulated and used" + , Option "" ["bibliography"] (ReqArg (\arg opt -> return opt{ optMetadata = addMetadata @@ -905,13 +915,15 @@ readMetaValue s = case decode (UTF8.fromString s) of usageMessage :: String -> [OptDescr (Opt -> IO Opt)] -> String usageMessage programName = usageInfo (programName ++ " [OPTIONS] [FILES]" ++ "\nInput formats: " ++ - (wrapWords 16 78 $ readers'names) ++ "\nOutput formats: " ++ + (wrapWords 16 78 $ readers'names) ++ + '\n' : replicate 16 ' ' ++ + "[ *only Pandoc's JSON version of native AST]" ++ "\nOutput formats: " ++ (wrapWords 16 78 $ writers'names) ++ '\n' : replicate 16 ' ' ++ - "[*for pdf output, use latex or beamer and -o FILENAME.pdf]\nOptions:") + "[**for pdf output, use latex or beamer and -o FILENAME.pdf]\nOptions:") where - writers'names = sort $ "pdf*" : map fst writers - readers'names = sort $ map fst readers + writers'names = sort $ "json*" : "pdf**" : delete "json" (map fst writers) + readers'names = sort $ "json*" : delete "json" (map fst readers) -- Determine default reader based on source file extensions defaultReaderName :: String -> [FilePath] -> String @@ -1080,6 +1092,7 @@ main = do , optCiteMethod = citeMethod , optListings = listings , optLaTeXEngine = latexEngine + , optLaTeXEngineArgs = latexEngineArgs , optSlideLevel = slideLevel , optSetextHeaders = setextHeaders , optAscii = ascii @@ -1312,7 +1325,8 @@ main = do writerReferenceODT = referenceODT, writerReferenceDocx = referenceDocx, writerMediaBag = media, - writerVerbose = verbose + writerVerbose = verbose, + writerLaTeXArgs = latexEngineArgs } diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 48803d36f..a5dcbfd0b 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -330,6 +330,7 @@ data WriterOptions = WriterOptions , writerReferenceDocx :: Maybe FilePath -- ^ Path to reference DOCX if specified , writerMediaBag :: MediaBag -- ^ Media collected by docx or epub reader , writerVerbose :: Bool -- ^ Verbose debugging output + , writerLaTeXArgs :: [String] -- ^ Flags to pass to latex-engine } deriving Show instance Default WriterOptions where @@ -374,6 +375,7 @@ instance Default WriterOptions where , writerReferenceDocx = Nothing , writerMediaBag = mempty , writerVerbose = False + , writerLaTeXArgs = [] } -- | Returns True if the given extension is enabled. diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index ea6699ac4..59a6ebede 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -71,7 +71,8 @@ makePDF :: String -- ^ pdf creator (pdflatex, lualatex, xelatex) makePDF program writer opts doc = withTempDir "tex2pdf." $ \tmpdir -> do doc' <- handleImages opts tmpdir doc let source = writer opts doc' - tex2pdf' (writerVerbose opts) tmpdir program source + args = writerLaTeXArgs opts + tex2pdf' (writerVerbose opts) args tmpdir program source handleImages :: WriterOptions -> FilePath -- ^ temp dir to store images @@ -132,15 +133,16 @@ convertImage tmpdir fname = doNothing = return (Right fname) tex2pdf' :: Bool -- ^ Verbose output + -> [String] -- ^ Arguments to the latex-engine -> FilePath -- ^ temp directory for output -> String -- ^ tex program -> String -- ^ tex source -> IO (Either ByteString ByteString) -tex2pdf' verbose tmpDir program source = do +tex2pdf' verbose args tmpDir program source = do let numruns = if "\\tableofcontents" `isInfixOf` source then 3 -- to get page numbers else 2 -- 1 run won't give you PDF bookmarks - (exit, log', mbPdf) <- runTeXProgram verbose program 1 numruns tmpDir source + (exit, log', mbPdf) <- runTeXProgram verbose program args 1 numruns tmpDir source case (exit, mbPdf) of (ExitFailure _, _) -> do let logmsg = extractMsg log' @@ -173,9 +175,9 @@ extractMsg log' = do -- Run a TeX program on an input bytestring and return (exit code, -- contents of stdout, contents of produced PDF if any). Rerun -- a fixed number of times to resolve references. -runTeXProgram :: Bool -> String -> Int -> Int -> FilePath -> String +runTeXProgram :: Bool -> String -> [String] -> Int -> Int -> FilePath -> String -> IO (ExitCode, ByteString, Maybe ByteString) -runTeXProgram verbose program runNumber numRuns tmpDir source = do +runTeXProgram verbose program args runNumber numRuns tmpDir source = do let file = tmpDir </> "input.tex" exists <- doesFileExist file unless exists $ UTF8.writeFile file source @@ -188,7 +190,7 @@ runTeXProgram verbose program runNumber numRuns tmpDir source = do let file' = file #endif let programArgs = ["-halt-on-error", "-interaction", "nonstopmode", - "-output-directory", tmpDir', file'] + "-output-directory", tmpDir', file'] ++ args env' <- getEnvironment let sep = searchPathSeparator:[] let texinputs = maybe (tmpDir' ++ sep) ((tmpDir' ++ sep) ++) @@ -212,7 +214,7 @@ runTeXProgram verbose program runNumber numRuns tmpDir source = do B.hPutStr stderr err putStr "\n" if runNumber <= numRuns - then runTeXProgram verbose program (runNumber + 1) numRuns tmpDir source + then runTeXProgram verbose program args (runNumber + 1) numRuns tmpDir source else do let pdfFile = replaceDirectory (replaceExtension file ".pdf") tmpDir pdfExists <- doesFileExist pdfFile diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 942b9f3b3..31ac37bf1 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -271,7 +271,9 @@ ignoreBlocks name = (name, doraw <|> (mempty <$ optargs)) blockCommands :: M.Map String (LP Blocks) blockCommands = M.fromList $ [ ("par", mempty <$ skipopts) - , ("title", mempty <$ (skipopts *> tok >>= addMeta "title")) + , ("title", mempty <$ (skipopts *> + (grouped inline >>= addMeta "title") + <|> (grouped block >>= addMeta "title"))) , ("subtitle", mempty <$ (skipopts *> tok >>= addMeta "subtitle")) , ("author", mempty <$ (skipopts *> authors)) -- -- in letter class, temp. store address & sig as title, author @@ -341,7 +343,7 @@ setCaption :: LP Blocks setCaption = do ils <- tok mblabel <- option Nothing $ - try $ spaces >> controlSeq "label" >> (Just <$> tok) + try $ spaces' >> controlSeq "label" >> (Just <$> tok) let ils' = case mblabel of Just lab -> ils <> spanWith ("",[],[("data-label", stringify lab)]) mempty @@ -369,7 +371,7 @@ section (ident, classes, kvs) lvl = do let lvl' = if hasChapters then lvl + 1 else lvl skipopts contents <- grouped inline - lab <- option ident $ try (spaces >> controlSeq "label" >> spaces >> braced) + lab <- option ident $ try (spaces' >> controlSeq "label" >> spaces' >> braced) attr' <- registerHeader (lab, classes, kvs) contents return $ headerWith attr' lvl' contents @@ -495,7 +497,7 @@ inlineCommands = M.fromList $ , ("v", option (str "v") $ try $ tok >>= accent hacek) , ("u", option (str "u") $ try $ tok >>= accent breve) , ("i", lit "i") - , ("\\", linebreak <$ (optional (bracketed inline) *> optional sp)) + , ("\\", linebreak <$ (optional (bracketed inline) *> spaces')) , (",", pure mempty) , ("@", pure mempty) , (" ", lit "\160") @@ -508,7 +510,7 @@ inlineCommands = M.fromList $ , ("thanks", (note . mconcat) <$> (char '{' *> manyTill block (char '}'))) , ("footnote", (note . mconcat) <$> (char '{' *> manyTill block (char '}'))) , ("verb", doverb) - , ("lstinline", doverb) + , ("lstinline", skipopts *> doverb) , ("Verb", doverb) , ("texttt", (code . stringify . toList) <$> tok) , ("url", (unescapeURL <$> braced) >>= \url -> @@ -1275,7 +1277,7 @@ complexNatbibCitation mode = try $ do parseAligns :: LP [Alignment] parseAligns = try $ do char '{' - let maybeBar = skipMany $ sp <|> () <$ char '|' <|> () <$ try (string "@{}") + let maybeBar = skipMany $ sp <|> () <$ char '|' <|> () <$ (char '@' >> braced) maybeBar let cAlign = AlignCenter <$ char 'c' let lAlign = AlignLeft <$ char 'l' @@ -1289,13 +1291,13 @@ parseAligns = try $ do return aligns' hline :: LP () -hline = () <$ (try $ spaces >> controlSeq "hline") +hline = () <$ (try $ spaces' *> controlSeq "hline" <* spaces') lbreak :: LP () -lbreak = () <$ (try $ spaces *> controlSeq "\\") +lbreak = () <$ (try $ spaces' *> controlSeq "\\" <* spaces') amp :: LP () -amp = () <$ (try $ spaces *> char '&') +amp = () <$ (try $ spaces' *> char '&') parseTableRow :: Int -- ^ number of columns -> LP [Blocks] @@ -1308,20 +1310,22 @@ parseTableRow cols = try $ do guard $ cells' /= [mempty] -- note: a & b in a three-column table leaves an empty 3rd cell: let cells'' = cells' ++ replicate (cols - numcells) mempty - spaces + spaces' return cells'' +spaces' :: LP () +spaces' = spaces *> skipMany (comment *> spaces) + simpTable :: Bool -> LP Blocks simpTable hasWidthParameter = try $ do - when hasWidthParameter $ () <$ (spaces >> tok) - spaces + when hasWidthParameter $ () <$ (spaces' >> tok) + skipopts aligns <- parseAligns let cols = length aligns optional hline header' <- option [] $ try (parseTableRow cols <* lbreak <* hline) rows <- sepEndBy (parseTableRow cols) (lbreak <* optional hline) - spaces - skipMany (comment *> spaces) + spaces' let header'' = if null header' then replicate cols mempty else header' diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index 9e6ad0e13..a36c2acde 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -1287,11 +1287,9 @@ pipeBreak = try $ do pipeTable :: MarkdownParser ([Alignment], [Double], F [Blocks], F [[Blocks]]) pipeTable = try $ do - (heads,aligns) <- try ( pipeBreak >>= \als -> - return (return $ replicate (length als) mempty, als)) - <|> ( pipeTableRow >>= \row -> pipeBreak >>= \als -> - - return (row, als) ) + (heads,aligns) <- pipeTableRow >>= \row -> + pipeBreak >>= \als -> + return (row, als) lines' <- sequence <$> many1 pipeTableRow let widths = replicate (length aligns) 0.0 return $ (aligns, widths, heads, lines') diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index e43b8a86c..d1ba35ba0 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -593,11 +593,17 @@ imageOption = <|> try (many1 (oneOf "x0123456789") <* string "px") <|> try (oneOfStrings ["link=","alt=","page=","class="] <* many (noneOf "|]")) +collapseUnderscores :: String -> String +collapseUnderscores [] = [] +collapseUnderscores ('_':'_':xs) = collapseUnderscores ('_':xs) +collapseUnderscores (x:xs) = x : collapseUnderscores xs + +addUnderscores :: String -> String +addUnderscores = collapseUnderscores . intercalate "_" . words + internalLink :: MWParser Inlines internalLink = try $ do sym "[[" - let addUnderscores x = let (pref,suff) = break (=='#') x - in pref ++ intercalate "_" (words suff) pagename <- unwords . words <$> many (noneOf "|]") label <- option (B.text pagename) $ char '|' *> ( (mconcat <$> many1 (notFollowedBy (char ']') *> inline)) diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index f16aed48d..4a523657c 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -1,6 +1,6 @@ {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} -{-# LANGUAGE FlexibleContexts #-} +{-# LANGUAGE MultiParamTypeClasses, FlexibleContexts, FlexibleInstances #-} {- Copyright (C) 2014 Albert Krewinkel <tarleb@moltkeplatz.de> @@ -49,7 +49,7 @@ import Control.Applicative ( Applicative, pure , (<$>), (<$), (<*>), (<*), (*>) ) import Control.Arrow (first) import Control.Monad (foldM, guard, liftM, liftM2, mplus, mzero, when) -import Control.Monad.Reader (Reader, runReader, ask, asks) +import Control.Monad.Reader (Reader, runReader, ask, asks, local) import Data.Char (isAlphaNum, toLower) import Data.Default import Data.List (intersperse, isPrefixOf, isSuffixOf) @@ -62,9 +62,11 @@ import Network.HTTP (urlEncode) readOrg :: ReaderOptions -- ^ Reader options -> String -- ^ String to parse (assuming @'\n'@ line endings) -> Pandoc -readOrg opts s = readWith parseOrg def{ orgStateOptions = opts } (s ++ "\n\n") +readOrg opts s = flip runReader def $ readWithM parseOrg def{ orgStateOptions = opts } (s ++ "\n\n") -type OrgParser = Parser [Char] OrgParserState +data OrgParserLocal = OrgParserLocal { orgLocalQuoteContext :: QuoteContext } + +type OrgParser = ParserT [Char] OrgParserState (Reader OrgParserLocal) parseOrg :: OrgParser Pandoc parseOrg = do @@ -125,6 +127,9 @@ data OrgParserState = OrgParserState , orgStateNotes' :: OrgNoteTable } +instance Default OrgParserLocal where + def = OrgParserLocal NoQuote + instance HasReaderOptions OrgParserState where extractReaderOptions = orgStateOptions @@ -138,6 +143,10 @@ 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 @@ -964,6 +973,7 @@ inline = , subscript , superscript , inlineLaTeX + , smart , symbol ] <* (guard =<< newlinesCountWithinLimits) <?> "inline" @@ -1270,12 +1280,16 @@ displayMath :: OrgParser (F Inlines) displayMath = return . B.displayMath <$> choice [ rawMathBetween "\\[" "\\]" , rawMathBetween "$$" "$$" ] + +updatePositions :: Char + -> OrgParser (Char) +updatePositions c = do + when (c `elem` emphasisPreChars) updateLastPreCharPos + when (c `elem` emphasisForbiddenBorderChars) updateLastForbiddenCharPos + return c + symbol :: OrgParser (F Inlines) symbol = return . B.str . (: "") <$> (oneOf specialChars >>= updatePositions) - where updatePositions c = do - when (c `elem` emphasisPreChars) updateLastPreCharPos - when (c `elem` emphasisForbiddenBorderChars) updateLastForbiddenCharPos - return c emphasisBetween :: Char -> OrgParser (F Inlines) @@ -1486,3 +1500,31 @@ inlineLaTeXCommand = try $ do count len anyChar return cs _ -> mzero + +smart :: OrgParser (F Inlines) +smart = do + getOption readerSmart >>= guard + doubleQuoted <|> singleQuoted <|> + choice (map (return <$>) [orgApostrophe, dash, ellipses]) + where orgApostrophe = + (char '\'' <|> char '\8217') <* updateLastPreCharPos + <* updateLastForbiddenCharPos + *> return (B.str "\x2019") + +singleQuoted :: OrgParser (F Inlines) +singleQuoted = try $ do + singleQuoteStart + withQuoteContext InSingleQuote $ + fmap B.singleQuoted . trimInlinesF . mconcat <$> + many1Till inline singleQuoteEnd + +-- doubleQuoted will handle regular double-quoted sections, as well +-- as dialogues with an open double-quote without a close double-quote +-- in the same paragraph. +doubleQuoted :: OrgParser (F Inlines) +doubleQuoted = try $ do + doubleQuoteStart + contents <- mconcat <$> many (try $ notFollowedBy doubleQuoteEnd >> inline) + (withQuoteContext InDoubleQuote $ (doubleQuoteEnd <* updateLastForbiddenCharPos) >> return + (fmap B.doubleQuoted . trimInlinesF $ contents)) + <|> (return $ return (B.str "\8220") <> contents) diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index cadac16a0..53dc931cc 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -446,13 +446,14 @@ blockToHtml opts (Para lst) = do contents <- inlineListToHtml opts lst return $ H.p contents blockToHtml opts (Div attr@(_,classes,_) bs) = do - contents <- blockListToHtml opts bs + let speakerNotes = "notes" `elem` classes + -- we don't want incremental output inside speaker notes, see #1394 + let opts' = if speakerNotes then opts{ writerIncremental = False } else opts + contents <- blockListToHtml opts' bs let contents' = nl opts >> contents >> nl opts return $ - if "notes" `elem` classes - then let opts' = opts{ writerIncremental = False } in - -- we don't want incremental output inside speaker notes - case writerSlideVariant opts of + if speakerNotes + then case writerSlideVariant opts of RevealJsSlides -> addAttrs opts' attr $ H5.aside $ contents' NoSlides -> addAttrs opts' attr $ H.div $ contents' _ -> mempty diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 15c6d9fb5..ebf7e20e2 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -509,7 +509,12 @@ pipeTable headless aligns rawHeaders rawRows = do AlignCenter -> ':':replicate w '-' ++ ":" AlignRight -> replicate (w + 1) '-' ++ ":" AlignDefault -> replicate (w + 2) '-' - let header = if headless then empty else torow rawHeaders + -- note: pipe tables can't completely lack a + -- header; for a headerless table, we need a header of empty cells. + -- see jgm/pandoc#1996. + let header = if headless + then torow (replicate (length aligns) empty) + else torow rawHeaders let border = nowrap $ text "|" <> hcat (intersperse (text "|") $ map toborder $ zip aligns widths) <> text "|" let body = vcat $ map torow rawRows diff --git a/tests/Tests/Readers/LaTeX.hs b/tests/Tests/Readers/LaTeX.hs index 8ff23ebc1..47916b0c0 100644 --- a/tests/Tests/Readers/LaTeX.hs +++ b/tests/Tests/Readers/LaTeX.hs @@ -7,6 +7,7 @@ import Tests.Helpers import Tests.Arbitrary() import Text.Pandoc.Builder import Text.Pandoc +import Data.Monoid (mempty) latex :: String -> Pandoc latex = readLaTeX def @@ -16,6 +17,10 @@ infix 4 =: => String -> (String, c) -> Test (=:) = test latex +simpleTable' :: [Alignment] -> [[Blocks]] -> Blocks +simpleTable' aligns = table "" (zip aligns (repeat 0.0)) + (map (const mempty) aligns) + tests :: [Test] tests = [ testGroup "basic" [ "simple" =: @@ -62,6 +67,40 @@ tests = [ testGroup "basic" "\\begin{lstlisting}\\end{lstlisting}" =?> codeBlock "" ] + , testGroup "tables" + [ "Single cell table" =: + "\\begin{tabular}{|l|}Test\\\\\\end{tabular}" =?> + simpleTable' [AlignLeft] [[plain "Test"]] + , "Multi cell table" =: + "\\begin{tabular}{|rl|}One & Two\\\\ \\end{tabular}" =?> + simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]] + , "Multi line table" =: + unlines [ "\\begin{tabular}{|c|}" + , "One\\\\" + , "Two\\\\" + , "Three\\\\" + , "\\end{tabular}" ] =?> + simpleTable' [AlignCenter] + [[plain "One"], [plain "Two"], [plain "Three"]] + , "Empty table" =: + "\\begin{tabular}{}\\end{tabular}" =?> + simpleTable' [] [] + , "Table with fixed column width" =: + "\\begin{tabular}{|p{5cm}r|}One & Two\\\\ \\end{tabular}" =?> + simpleTable' [AlignLeft,AlignRight] [[plain "One", plain "Two"]] + , "Table with empty column separators" =: + "\\begin{tabular}{@{}r@{}l}One & Two\\\\ \\end{tabular}" =?> + simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]] + , "Table with custom column separators" =: + unlines [ "\\begin{tabular}{@{($\\to$)}r@{\\hspace{2cm}}l}" + , "One&Two\\\\" + , "\\end{tabular}" ] =?> + simpleTable' [AlignRight,AlignLeft] [[plain "One", plain "Two"]] + , "Table with vertical alignment argument" =: + "\\begin{tabular}[t]{r|r}One & Two\\\\ \\end{tabular}" =?> + simpleTable' [AlignRight,AlignRight] [[plain "One", plain "Two"]] + ] + , testGroup "citations" [ natbibCitations , biblatexCitations diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs index 39c40cd45..c373d52cc 100644 --- a/tests/Tests/Readers/Org.hs +++ b/tests/Tests/Readers/Org.hs @@ -12,6 +12,9 @@ import Data.Monoid (mempty, mappend, mconcat) org :: String -> Pandoc org = readOrg def +orgSmart :: String -> Pandoc +orgSmart = readOrg def { readerSmart = True } + infix 4 =: (=:) :: ToString c => String -> (String, c) -> Test @@ -1152,4 +1155,25 @@ tests = ] in codeBlockWith ( "", classes, params) "code body\n" ] + , testGroup "Smart punctuation" + [ test orgSmart "quote before ellipses" + ("'...hi'" + =?> para (singleQuoted "…hi")) + + , test orgSmart "apostrophe before emph" + ("D'oh! A l'/aide/!" + =?> para ("D’oh! A l’" <> emph "aide" <> "!")) + + , test orgSmart "apostrophe in French" + ("À l'arrivée de la guerre, le thème de l'«impossibilité du socialisme»" + =?> para "À l’arrivée de la guerre, le thème de l’«impossibilité du socialisme»") + + , test orgSmart "Quotes cannot occur at the end of emphasized text" + ("/say \"yes\"/" =?> + para ("/say" <> space <> doubleQuoted "yes" <> "/")) + + , test orgSmart "Dashes are allowed at the borders of emphasis'" + ("/foo---/" =?> + para (emph "foo—")) + ] ] diff --git a/tests/pipe-tables.txt b/tests/pipe-tables.txt index ee8d54d9f..83debd595 100644 --- a/tests/pipe-tables.txt +++ b/tests/pipe-tables.txt @@ -1,7 +1,7 @@ Simplest table without caption: | Default1 | Default2 | Default3 | -|----------|----------|----------| + |----------|----------|----------| |12|12|12| |123|123|123| |1|1|1| @@ -27,6 +27,7 @@ Simple table without caption: Headerless table without caption: +| | | | |------:|:-----|:------:| |12|12|12| |123|123|123| @@ -48,5 +49,6 @@ One-column: Header-less one-column: +| | |:-:| |hi| |