aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/AsciiDoc.hs8
-rw-r--r--src/Text/Pandoc/Writers/DokuWiki.hs14
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs4
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs8
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs8
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs5
-rw-r--r--src/Text/Pandoc/Writers/Markdown.hs8
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs4
-rw-r--r--src/Text/Pandoc/Writers/RST.hs2
9 files changed, 27 insertions, 34 deletions
diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs
index 19112d8f5..8d36efeee 100644
--- a/src/Text/Pandoc/Writers/AsciiDoc.hs
+++ b/src/Text/Pandoc/Writers/AsciiDoc.hs
@@ -142,10 +142,10 @@ blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do
let len = offset contents
-- ident seem to be empty most of the time and asciidoc will generate them automatically
-- so lets make them not show up when null
- let identifier = if (null ident) then empty else ("[[" <> text ident <> "]]")
+ let identifier = if (null ident) then empty else ("[[" <> text ident <> "]]")
let setext = writerSetextHeaders opts
- return $
- (if setext
+ return $
+ (if setext
then
identifier $$ contents $$
(case level of
@@ -155,7 +155,7 @@ blockToAsciiDoc opts (Header level (ident,_,_) inlines) = do
4 -> text $ replicate len '+'
_ -> empty) <> blankline
else
- identifier $$ text (replicate level '=') <> space <> contents <> blankline)
+ identifier $$ text (replicate level '=') <> space <> contents <> blankline)
blockToAsciiDoc _ (CodeBlock (_,classes,_) str) = return $
flush (attrs <> dashes <> space <> attrs <> cr <> text str <>
cr <> dashes) <> blankline
diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs
index 61f548b0c..f04dab76d 100644
--- a/src/Text/Pandoc/Writers/DokuWiki.hs
+++ b/src/Text/Pandoc/Writers/DokuWiki.hs
@@ -44,7 +44,6 @@ import Text.Pandoc.Options
import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared
import Text.Pandoc.Templates (renderTemplate')
-import Text.Pandoc.Walk (query)
import Data.List ( intersect, intercalate )
import Network.URI ( isURI )
import Control.Monad.State
@@ -86,15 +85,6 @@ pandocToDokuWiki opts (Pandoc meta blocks) = do
escapeString :: String -> String
escapeString str = substitute "__" "%%__%%" ( substitute "**" "%%**%%" ( substitute "//" "%%//%%" str ) )
--- | Remove unsupported formatting from headings
-unfancy :: [Inline] -> [Inline]
-unfancy = query plainContent
-
-plainContent :: Inline -> [Inline]
-plainContent (Str x) = [Str x]
-plainContent Space = [Space]
-plainContent _ = []
-
-- | Convert Pandoc block element to DokuWiki.
blockToDokuWiki :: WriterOptions -- ^ Options
-> Block -- ^ Block element
@@ -136,7 +126,9 @@ blockToDokuWiki _ (RawBlock f str)
blockToDokuWiki _ HorizontalRule = return "\n----\n"
blockToDokuWiki opts (Header level _ inlines) = do
- contents <- inlineListToDokuWiki opts ( unfancy inlines )
+ -- emphasis, links etc. not allowed in headers, apparently,
+ -- so we remove formatting:
+ contents <- inlineListToDokuWiki opts $ removeFormatting inlines
let eqs = replicate ( 7 - level ) '='
return $ eqs ++ " " ++ contents ++ " " ++ eqs ++ "\n"
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index f7968884e..c53a0c13d 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -784,7 +784,7 @@ transformBlock opts mediaRef (RawBlock fmt raw)
| fmt == Format "html" = do
let tags = parseTags raw
tags' <- mapM (transformTag opts mediaRef) tags
- return $ RawBlock fmt (renderTags tags')
+ return $ RawBlock fmt (renderTags' tags')
transformBlock _ _ b = return b
transformInline :: WriterOptions
@@ -804,7 +804,7 @@ transformInline opts mediaRef (RawInline fmt raw)
| fmt == Format "html" = do
let tags = parseTags raw
tags' <- mapM (transformTag opts mediaRef) tags
- return $ RawInline fmt (renderTags tags')
+ return $ RawInline fmt (renderTags' tags')
transformInline _ _ x = return x
writeHtmlInline :: WriterOptions -> Inline -> String
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 9a26cf2ac..744e88c16 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -429,9 +429,11 @@ blockToHtml opts (Div attr@(_,classes,_) bs) = do
let contents' = nl opts >> contents >> nl opts
return $
if "notes" `elem` classes
- then case writerSlideVariant opts of
- RevealJsSlides -> addAttrs opts attr $ H5.aside $ contents'
- NoSlides -> addAttrs opts attr $ H.div $ contents'
+ then let opts' = opts{ writerIncremental = False } in
+ -- we don't want incremental output inside speaker notes
+ case writerSlideVariant opts of
+ RevealJsSlides -> addAttrs opts' attr $ H5.aside $ contents'
+ NoSlides -> addAttrs opts' attr $ H.div $ contents'
_ -> mempty
else addAttrs opts attr $ H.div $ contents'
blockToHtml _ (RawBlock f str)
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index 19d486b25..ae20efd4b 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -42,7 +42,7 @@ type WS a = State WriterState a
defaultWriterState :: WriterState
defaultWriterState = WriterState{
- blockStyles = Set.empty
+ blockStyles = Set.empty
, inlineStyles = Set.empty
, links = []
, listDepth = 1
@@ -267,7 +267,7 @@ hyperlinksToDoc (x:xs) = hyp x $$ hyperlinksToDoc xs
$ inTags False "BorderColor" [("type","enumeration")] (text "Black")
$$ (inTags False "Destination" [("type","object")]
$ text $ "HyperlinkURLDestination/"++(escapeStringForXML url))
-
+
-- | Convert a list of Pandoc blocks to ICML.
blocksToICML :: WriterOptions -> Style -> [Block] -> WS Doc
@@ -352,7 +352,7 @@ listItemsToICML opts listType style attribs (first:rest) = do
-- | Convert a list of blocks to ICML list items.
listItemToICML :: WriterOptions -> Style -> Bool-> Maybe ListAttributes -> [Block] -> WS Doc
listItemToICML opts style isFirst attribs item =
- let makeNumbStart (Just (beginsWith, numbStl, _)) =
+ let makeNumbStart (Just (beginsWith, numbStl, _)) =
let doN DefaultStyle = []
doN LowerRoman = [lowerRomanName]
doN UpperRoman = [upperRomanName]
@@ -467,7 +467,7 @@ parStyle opts style lst =
-- | Wrap a Doc in an ICML Character Style.
charStyle :: Style -> Doc -> WS Doc
-charStyle style content =
+charStyle style content =
let (stlStr, attrs) = styleToStrAttr style
doc = inTags True "CharacterStyleRange" attrs $ inTagsSimple "Content" $ flush content
in do
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 100bf900d..5bbe30fc8 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -471,19 +471,18 @@ blockToLaTeX (Table caption aligns widths heads rows) = do
captionText <- inlineListToLaTeX caption
let capt = if isEmpty captionText
then empty
- else text "\\addlinespace"
- $$ text "\\caption" <> braces captionText
+ else text "\\caption" <> braces captionText <> "\\\\"
rows' <- mapM (tableRowToLaTeX False aligns widths) rows
let colDescriptors = text $ concat $ map toColDescriptor aligns
modify $ \s -> s{ stTable = True }
return $ "\\begin{longtable}[c]" <>
braces ("@{}" <> colDescriptors <> "@{}")
-- the @{} removes extra space at beginning and end
+ $$ capt
$$ "\\toprule\\addlinespace"
$$ headers
$$ vcat rows'
$$ "\\bottomrule"
- $$ capt
$$ "\\end{longtable}"
toColDescriptor :: Alignment -> String
diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs
index a67271a5d..3beba3bdd 100644
--- a/src/Text/Pandoc/Writers/Markdown.hs
+++ b/src/Text/Pandoc/Writers/Markdown.hs
@@ -46,7 +46,7 @@ import Control.Monad.State
import qualified Data.Set as Set
import Text.Pandoc.Writers.HTML (writeHtmlString)
import Text.Pandoc.Readers.TeXMath (readTeXMath')
-import Text.HTML.TagSoup (renderTags, parseTags, isTagText, Tag(..))
+import Text.HTML.TagSoup (parseTags, isTagText, Tag(..))
import Network.URI (isURI)
import Data.Default
import Data.Yaml (Value(Object,String,Array,Bool,Number))
@@ -405,8 +405,8 @@ blockToMarkdown opts (CodeBlock attribs str) = return $
attrs = if isEnabled Ext_fenced_code_attributes opts
then nowrap $ " " <> attrsToMarkdown attribs
else case attribs of
- (_,[cls],_) -> " " <> text cls
- _ -> empty
+ (_,(cls:_),_) -> " " <> text cls
+ _ -> empty
blockToMarkdown opts (BlockQuote blocks) = do
st <- get
-- if we're writing literate haskell, put a space before the bird tracks
@@ -471,7 +471,7 @@ addMarkdownAttribute :: String -> String
addMarkdownAttribute s =
case span isTagText $ reverse $ parseTags s of
(xs,(TagOpen t attrs:rest)) ->
- renderTags $ reverse rest ++ (TagOpen t attrs' : reverse xs)
+ renderTags' $ reverse rest ++ (TagOpen t attrs' : reverse xs)
where attrs' = ("markdown","1"):[(x,y) | (x,y) <- attrs,
x /= "markdown"]
_ -> s
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index b6da2694c..e2b9a68f1 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -504,7 +504,7 @@ paraStyle parent attrs = do
tight = if t then [ ("fo:margin-top" , "0in" )
, ("fo:margin-bottom" , "0in" )]
else []
- indent = if (i /= 0 || b)
+ indent = if (i /= 0 || b)
then [ ("fo:margin-left" , indentVal)
, ("fo:margin-right" , "0in" )
, ("fo:text-indent" , "0in" )
@@ -534,7 +534,7 @@ paraTableStyles t s (a:xs)
[ ("fo:text-align", x)
, ("style:justify-single-word", "false")]
-data TextStyle = Italic | Bold | Strike | Sub | Sup | SmallC | Pre
+data TextStyle = Italic | Bold | Strike | Sub | Sup | SmallC | Pre
deriving ( Eq,Ord )
textStyleAttr :: TextStyle -> [(String,String)]
diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs
index 31c97349b..5e97d2ac3 100644
--- a/src/Text/Pandoc/Writers/RST.hs
+++ b/src/Text/Pandoc/Writers/RST.hs
@@ -174,7 +174,7 @@ blockToRST (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
let alt = ":alt: " <> if null tit then capt else text tit
return $ hang 3 ".. " $ fig $$ alt $+$ capt $$ blankline
blockToRST (Para inlines)
- | LineBreak `elem` inlines = do -- use line block if LineBreaks
+ | LineBreak `elem` inlines = do -- use line block if LineBreaks
lns <- mapM inlineListToRST $ splitBy (==LineBreak) inlines
return $ (vcat $ map (text "| " <>) lns) <> blankline
| otherwise = do