aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/OpenDocument.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/OpenDocument.hs')
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs26
1 files changed, 18 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index b38d250aa..0029c3296 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -64,6 +64,7 @@ data WriterState =
, stInDefinition :: Bool
, stTight :: Bool
, stFirstPara :: Bool
+ , stImageId :: Int
}
defaultWriterState :: WriterState
@@ -78,6 +79,7 @@ defaultWriterState =
, stInDefinition = False
, stTight = False
, stFirstPara = False
+ , stImageId = 1
}
when :: Bool -> Doc -> Doc
@@ -283,8 +285,12 @@ blocksToOpenDocument o b = vcat <$> mapM (blockToOpenDocument o) b
-- | Convert a Pandoc block element to OpenDocument.
blockToOpenDocument :: WriterOptions -> Block -> State WriterState Doc
blockToOpenDocument o bs
- | Plain b <- bs = inParagraphTags =<< inlinesToOpenDocument o b
- | Para b <- bs = inParagraphTags =<< inlinesToOpenDocument o b
+ | Plain b <- bs = if null b
+ then return empty
+ else inParagraphTags =<< inlinesToOpenDocument o b
+ | Para b <- bs = if null b
+ then return empty
+ else inParagraphTags =<< inlinesToOpenDocument o b
| Div _ xs <- bs = blocksToOpenDocument o xs
| Header i _ b <- bs = setFirstPara >>
(inHeaderTags i =<< inlinesToOpenDocument o b)
@@ -296,8 +302,8 @@ blockToOpenDocument o bs
| Table c a w h r <- bs = setFirstPara >> table c a w h r
| HorizontalRule <- bs = setFirstPara >> return (selfClosingTag "text:p"
[ ("text:style-name", "Horizontal_20_Line") ])
- | RawBlock f s <- bs = if f == "opendocument"
- then preformatted s
+ | RawBlock f s <- bs = if f == Format "opendocument"
+ then return $ text s
else return empty
| Null <- bs = return empty
| otherwise = return empty
@@ -376,11 +382,11 @@ inlineToOpenDocument o ils
| Code _ s <- ils = withTextStyle Pre $ inTextStyle $ preformatted s
| Math t s <- ils = inlinesToOpenDocument o (readTeXMath' t s)
| Cite _ l <- ils = inlinesToOpenDocument o l
- | RawInline f s <- ils = if f == "opendocument" || f == "html"
- then withTextStyle Pre $ inTextStyle $ preformatted s
+ | RawInline f s <- ils = if f == Format "opendocument"
+ then return $ text s
else return empty
| Link l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l
- | Image _ (s,t) <- ils = return $ mkImg s t
+ | Image _ (s,t) <- ils = mkImg s t
| Note l <- ils = mkNote l
| otherwise = return empty
where
@@ -389,7 +395,11 @@ inlineToOpenDocument o ils
, ("xlink:href" , s )
, ("office:name", t )
] . inSpanTags "Definition"
- mkImg s t = inTags False "draw:frame" (attrsFromTitle t) $
+ mkImg s t = do
+ id' <- gets stImageId
+ modify (\st -> st{ stImageId = id' + 1 })
+ return $ inTags False "draw:frame"
+ (("draw:name", "img" ++ show id'):attrsFromTitle t) $
selfClosingTag "draw:image" [ ("xlink:href" , s )
, ("xlink:type" , "simple")
, ("xlink:show" , "embed" )