aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
m---------data/templates18
-rw-r--r--pandoc.cabal6
-rw-r--r--src/Text/Pandoc/Readers/RST.hs34
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs16
-rw-r--r--tests/Tests/Arbitrary.hs11
-rw-r--r--tests/rst-reader.native2
-rw-r--r--tests/writer.context10
-rw-r--r--tests/writer.latex22
8 files changed, 50 insertions, 69 deletions
diff --git a/data/templates b/data/templates
-Subproject 2afb0792ba411006f51cd078fb7c409f0df19db
+Subproject c3a7937a2852e654da23df978b7abf79955008b
diff --git a/pandoc.cabal b/pandoc.cabal
index 732b7cf50..002d1671c 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -221,7 +221,7 @@ Library
xml >= 1.3.12 && < 1.4,
random >= 1 && < 1.1,
extensible-exceptions >= 0.1 && < 0.2,
- pandoc-types >= 1.12.3 && < 1.13,
+ pandoc-types >= 1.12.3.3 && < 1.13,
aeson >= 0.7 && < 0.8,
tagsoup >= 0.13.1 && < 0.14,
base64-bytestring >= 0.1 && < 1.1,
@@ -319,7 +319,7 @@ Library
Executable pandoc
Build-Depends: pandoc,
- pandoc-types >= 1.12.3 && < 1.13,
+ pandoc-types >= 1.12.3.3 && < 1.13,
base >= 4.2 && <5,
directory >= 1 && < 1.3,
filepath >= 1.1 && < 1.4,
@@ -364,7 +364,7 @@ Test-Suite test-pandoc
Build-Depends: base >= 4.2 && < 5,
syb >= 0.1 && < 0.5,
pandoc,
- pandoc-types >= 1.12.3 && < 1.13,
+ pandoc-types >= 1.12.3.3 && < 1.13,
bytestring >= 0.9 && < 0.11,
text >= 0.11 && < 1.2,
directory >= 1 && < 1.3,
diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs
index 7785861cc..54b6fa34a 100644
--- a/src/Text/Pandoc/Readers/RST.hs
+++ b/src/Text/Pandoc/Readers/RST.hs
@@ -113,15 +113,16 @@ titleTransform (bs, meta) =
metaFromDefList :: [([Inline], [[Block]])] -> Meta -> Meta
metaFromDefList ds meta = adjustAuthors $ foldr f meta ds
where f (k,v) = setMeta (map toLower $ stringify k) (mconcat $ map fromList v)
- adjustAuthors (Meta metamap) = Meta $ M.adjust toPlain "author"
+ adjustAuthors (Meta metamap) = Meta $ M.adjust splitAuthors "author"
$ M.adjust toPlain "date"
$ M.adjust toPlain "title"
- $ M.adjust splitAuthors "authors"
+ $ M.mapKeys (\k -> if k == "authors" then "author" else k)
$ metamap
toPlain (MetaBlocks [Para xs]) = MetaInlines xs
toPlain x = x
- splitAuthors (MetaBlocks [Para xs]) = MetaList $ map MetaInlines
- $ splitAuthors' xs
+ splitAuthors (MetaBlocks [Para xs])
+ = MetaList $ map MetaInlines
+ $ splitAuthors' xs
splitAuthors x = x
splitAuthors' = map normalizeSpaces .
splitOnSemi . concatMap factorSemi
@@ -185,22 +186,22 @@ block = choice [ codeBlock
-- field list
--
-rawFieldListItem :: String -> RSTParser (String, String)
-rawFieldListItem indent = try $ do
- string indent
+rawFieldListItem :: Int -> RSTParser (String, String)
+rawFieldListItem minIndent = try $ do
+ indent <- length <$> many (char ' ')
+ guard $ indent >= minIndent
char ':'
name <- many1Till (noneOf "\n") (char ':')
(() <$ lookAhead newline) <|> skipMany1 spaceChar
first <- anyLine
- rest <- option "" $ try $ do lookAhead (string indent >> spaceChar)
+ rest <- option "" $ try $ do lookAhead (count indent (char ' ') >> spaceChar)
indentedBlock
let raw = (if null first then "" else (first ++ "\n")) ++ rest ++ "\n"
return (name, raw)
-fieldListItem :: String
- -> RSTParser (Inlines, [Blocks])
-fieldListItem indent = try $ do
- (name, raw) <- rawFieldListItem indent
+fieldListItem :: Int -> RSTParser (Inlines, [Blocks])
+fieldListItem minIndent = try $ do
+ (name, raw) <- rawFieldListItem minIndent
let term = B.str name
contents <- parseFromString parseBlocks raw
optional blanklines
@@ -208,7 +209,7 @@ fieldListItem indent = try $ do
fieldList :: RSTParser Blocks
fieldList = try $ do
- indent <- lookAhead $ many spaceChar
+ indent <- length <$> lookAhead (many spaceChar)
items <- many1 $ fieldListItem indent
case items of
[] -> return mempty
@@ -521,11 +522,11 @@ directive' = do
skipMany spaceChar
top <- many $ satisfy (/='\n')
<|> try (char '\n' <*
- notFollowedBy' (rawFieldListItem " ") <*
+ notFollowedBy' (rawFieldListItem 3) <*
count 3 (char ' ') <*
notFollowedBy blankline)
newline
- fields <- many $ rawFieldListItem " "
+ fields <- many $ rawFieldListItem 3
body <- option "" $ try $ blanklines >> indentedBlock
optional blanklines
let body' = body ++ "\n\n"
@@ -576,6 +577,9 @@ directive' = do
role -> role })
"code" -> codeblock (lookup "number-lines" fields) (trim top) body
"code-block" -> codeblock (lookup "number-lines" fields) (trim top) body
+ "aafig" -> do
+ let attribs = ("", ["aafig"], map (\(k,v) -> (k, trimr v)) fields)
+ return $ B.codeBlockWith attribs $ stripTrailingNewlines body
"math" -> return $ B.para $ mconcat $ map B.displayMath
$ toChunks $ top ++ "\n\n" ++ body
"figure" -> do
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 3095cf508..cec420dcf 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -35,7 +35,7 @@ import Text.Pandoc.Writers.Shared
import Text.Pandoc.Options
import Text.Pandoc.Walk (query)
import Text.Printf ( printf )
-import Data.List ( intercalate, isPrefixOf )
+import Data.List ( intercalate )
import Control.Monad.State
import Text.Pandoc.Pretty
import Text.Pandoc.Templates ( renderTemplate' )
@@ -283,14 +283,6 @@ inlineToConTeXt (RawInline "tex" str) = return $ text str
inlineToConTeXt (RawInline _ _) = return empty
inlineToConTeXt (LineBreak) = return $ text "\\crlf" <> cr
inlineToConTeXt Space = return space
--- autolink
-inlineToConTeXt (Link [Str str] (src, tit))
- | if "mailto:" `isPrefixOf` src
- then src == escapeURI ("mailto:" ++ str)
- else src == escapeURI str =
- inlineToConTeXt (Link
- [RawInline "context" "\\hyphenatedurl{", Str str, RawInline "context" "}"]
- (src, tit))
-- Handle HTML-like internal document references to sections
inlineToConTeXt (Link txt (('#' : ref), _)) = do
opts <- gets stOptions
@@ -305,6 +297,7 @@ inlineToConTeXt (Link txt (('#' : ref), _)) = do
<> brackets (text ref)
inlineToConTeXt (Link txt (src, _)) = do
+ let isAutolink = txt == [Str src]
st <- get
let next = stNextRef st
put $ st {stNextRef = next + 1}
@@ -313,8 +306,9 @@ inlineToConTeXt (Link txt (src, _)) = do
return $ "\\useURL"
<> brackets (text ref)
<> brackets (text $ escapeStringUsing [('#',"\\#"),('%',"\\%")] src)
- <> brackets empty
- <> brackets label
+ <> (if isAutolink
+ then empty
+ else brackets empty <> brackets label)
<> "\\from"
<> brackets (text ref)
inlineToConTeXt (Image _ (src, _)) = do
diff --git a/tests/Tests/Arbitrary.hs b/tests/Tests/Arbitrary.hs
index 31c0cb46a..3675d97bf 100644
--- a/tests/Tests/Arbitrary.hs
+++ b/tests/Tests/Arbitrary.hs
@@ -49,7 +49,7 @@ arbInline n = frequency $ [ (60, liftM Str realString)
, (10, liftM Strikeout $ arbInlines (n-1))
, (10, liftM Superscript $ arbInlines (n-1))
, (10, liftM Subscript $ arbInlines (n-1))
--- , (10, liftM SmallCaps $ arbInlines (n-1))
+ , (10, liftM SmallCaps $ arbInlines (n-1))
, (10, do x1 <- arbitrary
x2 <- arbInlines (n-1)
return $ Quoted x1 x2)
@@ -64,6 +64,7 @@ arbInline n = frequency $ [ (60, liftM Str realString)
x3 <- realString
x2 <- liftM escapeURI realString
return $ Image x1 (x2,x3))
+ , (2, liftM2 Cite arbitrary (arbInlines 1))
, (2, liftM Note $ resize 3 $ listOf1 $ arbBlock (n-1))
]
@@ -111,7 +112,6 @@ instance Arbitrary Pandoc where
arbitrary = resize 8 $ liftM normalize
$ liftM2 Pandoc arbitrary arbitrary
-{-
instance Arbitrary CitationMode where
arbitrary
= do x <- choose (0 :: Int, 2)
@@ -123,14 +123,13 @@ instance Arbitrary CitationMode where
instance Arbitrary Citation where
arbitrary
- = do x1 <- liftM (filter (`notElem` ",;]@ \t\n")) arbitrary
- x2 <- arbitrary
- x3 <- arbitrary
+ = do x1 <- listOf $ elements $ ['a'..'z'] ++ ['0'..'9'] ++ ['_']
+ x2 <- arbInlines 1
+ x3 <- arbInlines 1
x4 <- arbitrary
x5 <- arbitrary
x6 <- arbitrary
return (Citation x1 x2 x3 x4 x5 x6)
--}
instance Arbitrary MathType where
arbitrary
diff --git a/tests/rst-reader.native b/tests/rst-reader.native
index fd48bc60c..c77d15775 100644
--- a/tests/rst-reader.native
+++ b/tests/rst-reader.native
@@ -1,4 +1,4 @@
-Pandoc (Meta {unMeta = fromList [("authors",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("revision",MetaBlocks [Para [Str "3"]]),("subtitle",MetaInlines [Str "Subtitle"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
+Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("revision",MetaBlocks [Para [Str "3"]]),("subtitle",MetaInlines [Str "Subtitle"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
[Header 1 ("level-one-header",[],[]) [Str "Level",Space,Str "one",Space,Str "header"]
,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,Header 2 ("level-two-header",[],[]) [Str "Level",Space,Str "two",Space,Str "header"]
diff --git a/tests/writer.context b/tests/writer.context
index 0b031fd76..0c5024d89 100644
--- a/tests/writer.context
+++ b/tests/writer.context
@@ -813,24 +813,22 @@ braces]\from[url26].
\subsection[autolinks]{Autolinks}
-With an ampersand:
-\useURL[url27][http://example.com/?foo=1&bar=2][][\hyphenatedurl{http://example.com/?foo=1&bar=2}]\from[url27]
+With an ampersand: \useURL[url27][http://example.com/?foo=1&bar=2]\from[url27]
\startitemize[packed]
\item
In a list?
\item
- \useURL[url28][http://example.com/][][\hyphenatedurl{http://example.com/}]\from[url28]
+ \useURL[url28][http://example.com/]\from[url28]
\item
It should.
\stopitemize
An e-mail address:
-\useURL[url29][mailto:nobody@nowhere.net][][\hyphenatedurl{nobody@nowhere.net}]\from[url29]
+\useURL[url29][mailto:nobody@nowhere.net][][nobody@nowhere.net]\from[url29]
\startblockquote
-Blockquoted:
-\useURL[url30][http://example.com/][][\hyphenatedurl{http://example.com/}]\from[url30]
+Blockquoted: \useURL[url30][http://example.com/]\from[url30]
\stopblockquote
Auto-links should not occur here: \type{<http://example.com/>}
diff --git a/tests/writer.latex b/tests/writer.latex
index 4cb989fba..a2f973854 100644
--- a/tests/writer.latex
+++ b/tests/writer.latex
@@ -22,24 +22,14 @@
\IfFileExists{microtype.sty}{\usepackage{microtype}}{}
\usepackage{fancyvrb}
\usepackage{graphicx}
-% Redefine \includegraphics so that, unless explicit options are
-% given, the image width will not exceed the width of the page.
-% Images get their normal width if they fit onto the page, but
-% are scaled down if they would overflow the margins.
\makeatletter
-\def\ScaleIfNeeded{%
- \ifdim\Gin@nat@width>\linewidth
- \linewidth
- \else
- \Gin@nat@width
- \fi
-}
+\def\maxwidth{\ifdim\Gin@nat@width>\linewidth\linewidth\else\Gin@nat@width\fi}
+\def\maxheight{\ifdim\Gin@nat@height>\textheight\textheight\else\Gin@nat@height\fi}
\makeatother
-\let\Oldincludegraphics\includegraphics
-{%
- \catcode`\@=11\relax%
- \gdef\includegraphics{\@ifnextchar[{\Oldincludegraphics}{\Oldincludegraphics[width=\ScaleIfNeeded]}}%
-}%
+% Scale images if necessary, so that they will not overflow the page
+% margins by default, and it is still possible to overwrite the defaults
+% using explicit options in \includegraphics[width, height, ...]{}
+\setkeys{Gin}{width=\maxwidth,height=\maxheight,keepaspectratio}
\ifxetex
\usepackage[setpagesize=false, % page size defined by xetex
unicode=false, % unicode breaks when used with xetex