aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README4
-rw-r--r--data/sample.lua8
-rw-r--r--pandoc.cabal4
-rw-r--r--src/Text/Pandoc/Readers/Odt/StyleReader.hs12
-rw-r--r--src/Text/Pandoc/Readers/Org.hs2
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs2
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs7
-rw-r--r--src/Text/Pandoc/Writers/RST.hs8
-rw-r--r--stack.yaml3
-rw-r--r--tests/Tests/Readers/Org.hs9
-rw-r--r--tests/Tests/Writers/Docx.hs5
-rw-r--r--tests/Tests/Writers/RST.hs25
12 files changed, 71 insertions, 18 deletions
diff --git a/README b/README
index da9bfea03..8921d076e 100644
--- a/README
+++ b/README
@@ -246,8 +246,8 @@ General options
in Windows 7. (You can find the default user data directory
on your system by looking at the output of `pandoc --version`.)
- A `reference.odt`, `reference.docx`, `default.csl`,
- `epub.css`, `templates`, `slidy`, `slideous`, or `s5` directory
+ A `reference.odt`, `reference.docx`, `epub.css`, `templates`,
+ `slidy`, `slideous`, or `s5` directory
placed in this directory will override pandoc's normal defaults.
`--bash-completiion`
diff --git a/data/sample.lua b/data/sample.lua
index f5c17839e..fa265d04d 100644
--- a/data/sample.lua
+++ b/data/sample.lua
@@ -84,7 +84,7 @@ function Doc(body, metadata, variables)
end
add('</ol>')
end
- return table.concat(buffer,'\n')
+ return table.concat(buffer,'\n') .. '\n'
end
-- The functions that follow render corresponding pandoc elements.
@@ -251,6 +251,12 @@ function html_align(align)
end
end
+function CaptionedImage(src, tit, caption)
+ return '<div class="figure">\n<img src="' .. escape(src,true) ..
+ '" title="' .. escape(tit,true) .. '"/>\n' ..
+ '<p class="caption">' .. caption .. '</p>\n</div>'
+end
+
-- Caption is a string, aligns is an array of strings,
-- widths is an array of floats, headers is an array of
-- strings, rows is an array of arrays of strings.
diff --git a/pandoc.cabal b/pandoc.cabal
index f6884adb2..0e1e75897 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -260,7 +260,7 @@ Library
random >= 1 && < 1.2,
extensible-exceptions >= 0.1 && < 0.2,
pandoc-types >= 1.12.4 && < 1.13,
- aeson >= 0.7 && < 0.10,
+ aeson >= 0.7 && < 0.11,
tagsoup >= 0.13.1 && < 0.14,
base64-bytestring >= 0.1 && < 1.1,
zlib >= 0.5 && < 0.7,
@@ -410,7 +410,7 @@ Executable pandoc
bytestring >= 0.9 && < 0.11,
extensible-exceptions >= 0.1 && < 0.2,
highlighting-kate >= 0.6 && < 0.7,
- aeson >= 0.7.0.5 && < 0.10,
+ aeson >= 0.7.0.5 && < 0.11,
yaml >= 0.8.8.2 && < 0.9,
containers >= 0.1 && < 0.6,
HTTP >= 4000.0.5 && < 4000.3
diff --git a/src/Text/Pandoc/Readers/Odt/StyleReader.hs b/src/Text/Pandoc/Readers/Odt/StyleReader.hs
index 1cf87cc59..b451e52a0 100644
--- a/src/Text/Pandoc/Readers/Odt/StyleReader.hs
+++ b/src/Text/Pandoc/Readers/Odt/StyleReader.hs
@@ -362,11 +362,11 @@ instance Read XslUnit where
estimateInMillimeter :: Int -> XslUnit -> Int
estimateInMillimeter n XslUnitMM = n
estimateInMillimeter n XslUnitCM = n * 10
-estimateInMillimeter n XslUnitInch = n * 25 -- * 25.4
-estimateInMillimeter n XslUnitPoints = n `div` 3 -- * 1/72 * 25.4
-estimateInMillimeter n XslUnitPica = n * 4 -- * 12 * 1/72 * 25.4
-estimateInMillimeter n XslUnitPixel = n `div`3 -- * 1/72 * 25.4
-estimateInMillimeter n XslUnitEM = n * 7 -- * 16 * 1/72 * 25.4
+estimateInMillimeter n XslUnitInch = n * 25 -- \* 25.4
+estimateInMillimeter n XslUnitPoints = n `div` 3 -- \* 1/72 * 25.4
+estimateInMillimeter n XslUnitPica = n * 4 -- \* 12 * 1/72 * 25.4
+estimateInMillimeter n XslUnitPixel = n `div`3 -- \* 1/72 * 25.4
+estimateInMillimeter n XslUnitEM = n * 7 -- \* 16 * 1/72 * 25.4
----
@@ -385,7 +385,7 @@ getListLevelStyle level ListStyle{..} =
let (lower , exactHit , _) = M.splitLookup level levelStyles
in exactHit <|> fmap fst (M.maxView lower)
-- findBy (`M.lookup` levelStyles) [level, (level-1) .. 1]
- -- ^ simpler, but in general less efficient
+ -- \^ simpler, but in general less efficient
data ListLevelStyle = ListLevelStyle { listLevelType :: ListLevelType
, listItemPrefix :: Maybe String
diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index 55ac92bcb..388a8f880 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -409,7 +409,7 @@ verseBlock blkProp = try $ do
ignHeaders
content <- rawBlockContent blkProp
fmap B.para . mconcat . intersperse (pure B.linebreak)
- <$> mapM (parseFromString parseInlines) (lines content)
+ <$> mapM (parseFromString parseInlines) (map (++ "\n") . lines $ content)
exportsCode :: [(String, String)] -> Bool
exportsCode attrs = not (("rundoc-exports", "none") `elem` attrs
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 0cb313e7b..5870844a4 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -211,7 +211,7 @@ writeDocx opts doc@(Pandoc meta _) = do
let doc' = walk fixDisplayMath $ doc
username <- lookup "USERNAME" <$> getEnvironment
utctime <- getCurrentTime
- distArchive <- getDefaultReferenceDocx Nothing
+ distArchive <- getDefaultReferenceDocx datadir
refArchive <- case writerReferenceDocx opts of
Just f -> liftM (toArchive . toLazy) $ B.readFile f
Nothing -> getDefaultReferenceDocx datadir
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index 804f4101d..5e7748efb 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -258,10 +258,13 @@ tableOfContents opts headers =
-- | Converts an Element to a list item for a table of contents,
elementToListItem :: WriterOptions -> Element -> [Block]
-elementToListItem opts (Sec lev _ _ headerText subsecs)
- = Plain headerText :
+elementToListItem opts (Sec lev _nums (ident,_,_) headerText subsecs)
+ = Plain headerLink :
[ BulletList (map (elementToListItem opts) subsecs) |
not (null subsecs) && lev < writerTOCDepth opts ]
+ where headerLink = if null ident
+ then headerText
+ else [Link headerText ('#':ident, "")]
elementToListItem _ (Blk _) = []
attrsToMarkdown :: Attr -> Doc
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index fae908f30..754aee29c 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -81,7 +81,8 @@ pandocToRST (Pandoc meta blocks) = do
(fmap (render colwidth) . blockListToRST)
(fmap (trimr . render colwidth) . inlineListToRST)
$ deleteMeta "title" $ deleteMeta "subtitle" meta
- body <- blockListToRST' True $ normalizeHeadings 1 blocks
+ let minLev = findMinHeadingLevel Nothing blocks
+ body <- blockListToRST' True $ normalizeHeadings minLev blocks
notes <- liftM (reverse . stNotes) get >>= notesToRST
-- note that the notes may contain refs, so we do them first
refs <- liftM (reverse . stLinks) get >>= refsToRST
@@ -107,6 +108,11 @@ pandocToRST (Pandoc meta blocks) = do
headerLtEq _ _ = False
normalizeHeadings lev (b:bs) = b:normalizeHeadings lev bs
normalizeHeadings _ [] = []
+ findMinHeadingLevel Nothing (Header l _a _i:bs) = findMinHeadingLevel (Just l) bs
+ findMinHeadingLevel (Just ol) (Header l _a _i:bs) =
+ findMinHeadingLevel (Just $ if ol>l then l else ol) bs
+ findMinHeadingLevel l (_:bs) = findMinHeadingLevel l bs
+ findMinHeadingLevel l [] = fromMaybe 1 l
-- | Return RST representation of reference key table.
refsToRST :: Refs -> State WriterState Doc
diff --git a/stack.yaml b/stack.yaml
index 15c68a265..bddb744d4 100644
--- a/stack.yaml
+++ b/stack.yaml
@@ -7,5 +7,6 @@ flags:
network-uri: true
packages:
- '.'
+- 'https://hackage.haskell.org/package/pandoc-types-1.12.4.6/pandoc-types-1.12.4.6.tar.gz'
extra-deps: []
-resolver: lts-3.1
+resolver: lts-3.4
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index 5eed2c9f4..52aaea52e 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -1143,6 +1143,15 @@ tests =
]
]
+ , "Verse block with newlines" =:
+ unlines [ "#+BEGIN_VERSE"
+ , "foo"
+ , ""
+ , "bar"
+ , "#+END_VERSE"
+ ] =?>
+ para ("foo" <> linebreak <> linebreak <> "bar")
+
, "LaTeX fragment" =:
unlines [ "\\begin{equation}"
, "X_i = \\begin{cases}"
diff --git a/tests/Tests/Writers/Docx.hs b/tests/Tests/Writers/Docx.hs
index 068c5a935..8dba0ea55 100644
--- a/tests/Tests/Writers/Docx.hs
+++ b/tests/Tests/Writers/Docx.hs
@@ -8,6 +8,7 @@ import Test.Framework
import Text.Pandoc.Readers.Docx
import Text.Pandoc.Writers.Docx
import Text.Pandoc.Error
+import System.FilePath ((</>))
type Options = (WriterOptions, ReaderOptions)
@@ -16,7 +17,9 @@ compareOutput :: Options
-> IO (Pandoc, Pandoc)
compareOutput opts nativeFile = do
nf <- Prelude.readFile nativeFile
- df <- writeDocx (fst opts) (handleError $ readNative nf)
+ let wopts = fst opts
+ df <- writeDocx wopts{writerUserDataDir = Just (".." </> "data")}
+ (handleError $ readNative nf)
let (p, _) = handleError $ readDocx (snd opts) df
return (p, handleError $ readNative nf)
diff --git a/tests/Tests/Writers/RST.hs b/tests/Tests/Writers/RST.hs
index 2a511782f..bb7b2a446 100644
--- a/tests/Tests/Writers/RST.hs
+++ b/tests/Tests/Writers/RST.hs
@@ -75,5 +75,30 @@ tests = [ testGroup "rubrics"
, ""
, "Header 2"
, "--------"]
+ , "minimal heading levels" =:
+ header 2 (text "Header 1") <>
+ header 3 (text "Header 2") <>
+ header 2 (text "Header 1") <>
+ header 4 (text "Header 2") <>
+ header 5 (text "Header 3") <>
+ header 3 (text "Header 2") =?>
+ unlines
+ [ "Header 1"
+ , "--------"
+ , ""
+ , "Header 2"
+ , "~~~~~~~~"
+ , ""
+ , "Header 1"
+ , "--------"
+ , ""
+ , "Header 2"
+ , "~~~~~~~~"
+ , ""
+ , "Header 3"
+ , "^^^^^^^^"
+ , ""
+ , "Header 2"
+ , "~~~~~~~~"]
]
]