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.hs84
1 files changed, 41 insertions, 43 deletions
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index ebe678dc0..e0434c630 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -39,7 +39,7 @@ import Text.Pandoc.Pretty
import Text.Printf ( printf )
import Control.Arrow ( (***), (>>>) )
import Control.Monad.State hiding ( when )
-import Data.Char (chr, isDigit)
+import Data.Char (chr)
import qualified Data.Map as Map
import Text.Pandoc.Writers.Shared
@@ -175,7 +175,7 @@ handleSpaces s
-- | Convert Pandoc document to string in OpenDocument format.
writeOpenDocument :: WriterOptions -> Pandoc -> String
writeOpenDocument opts (Pandoc meta blocks) =
- let colwidth = if writerWrapText opts
+ let colwidth = if writerWrapText opts == WrapAuto
then Just $ writerColumns opts
else Nothing
render' = render colwidth
@@ -191,8 +191,7 @@ writeOpenDocument opts (Pandoc meta blocks) =
listStyle (n,l) = inTags True "text:list-style"
[("style:name", "L" ++ show n)] (vcat l)
listStyles = map listStyle (stListStyles s)
- automaticStyles = inTagsIndented "office:automatic-styles" $ vcat $
- reverse $ styles ++ listStyles
+ automaticStyles = vcat $ reverse $ styles ++ listStyles
context = defField "body" body
$ defField "automatic-styles" (render' automaticStyles)
$ metadata
@@ -287,8 +286,8 @@ blockToOpenDocument o bs
| Plain b <- bs = if null b
then return empty
else inParagraphTags =<< inlinesToOpenDocument o b
- | Para [Image c (s,'f':'i':'g':':':t)] <- bs
- = figure c s t
+ | Para [Image attr c (s,'f':'i':'g':':':t)] <- bs
+ = figure attr c s t
| Para b <- bs = if null b
then return empty
else inParagraphTags =<< inlinesToOpenDocument o b
@@ -343,10 +342,10 @@ blockToOpenDocument o bs
return $ inTags True "table:table" [ ("table:name" , name)
, ("table:style-name", name)
] (vcat columns $$ th $$ vcat tr) $$ captionDoc
- figure caption source title | null caption =
- withParagraphStyle o "Figure" [Para [Image caption (source,title)]]
+ figure attr caption source title | null caption =
+ withParagraphStyle o "Figure" [Para [Image attr caption (source,title)]]
| otherwise = do
- imageDoc <- withParagraphStyle o "FigureWithCaption" [Para [Image caption (source,title)]]
+ imageDoc <- withParagraphStyle o "FigureWithCaption" [Para [Image attr caption (source,title)]]
captionDoc <- withParagraphStyle o "FigureCaption" [Para caption]
return $ imageDoc $$ captionDoc
@@ -375,38 +374,48 @@ inlinesToOpenDocument o l = hcat <$> mapM (inlineToOpenDocument o) l
-- | Convert an inline element to OpenDocument.
inlineToOpenDocument :: WriterOptions -> Inline -> State WriterState Doc
inlineToOpenDocument o ils
- | Space <- ils = inTextStyle space
- | Span _ xs <- ils = inlinesToOpenDocument o xs
- | LineBreak <- ils = return $ selfClosingTag "text:line-break" []
- | Str s <- ils = inTextStyle $ handleSpaces $ escapeStringForXML s
- | Emph l <- ils = withTextStyle Italic $ inlinesToOpenDocument o l
- | Strong l <- ils = withTextStyle Bold $ inlinesToOpenDocument o l
- | Strikeout l <- ils = withTextStyle Strike $ inlinesToOpenDocument o l
- | Superscript l <- ils = withTextStyle Sup $ inlinesToOpenDocument o l
- | Subscript l <- ils = withTextStyle Sub $ inlinesToOpenDocument o l
- | SmallCaps l <- ils = withTextStyle SmallC $ inlinesToOpenDocument o l
- | Quoted t l <- ils = inQuotes t <$> inlinesToOpenDocument o l
- | Code _ s <- ils = withTextStyle Pre $ inTextStyle $ preformatted s
- | Math t s <- ils = inlinesToOpenDocument o (texMathToInlines t s)
- | Cite _ l <- ils = inlinesToOpenDocument o l
- | 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 = mkImg s t
- | Note l <- ils = mkNote l
- | otherwise = return empty
+ = case ils of
+ Space -> inTextStyle space
+ SoftBreak
+ | writerWrapText o == WrapPreserve
+ -> inTextStyle (preformatted "\n")
+ | otherwise -> inTextStyle space
+ Span _ xs -> inlinesToOpenDocument o xs
+ LineBreak -> return $ selfClosingTag "text:line-break" []
+ Str s -> inTextStyle $ handleSpaces $ escapeStringForXML s
+ Emph l -> withTextStyle Italic $ inlinesToOpenDocument o l
+ Strong l -> withTextStyle Bold $ inlinesToOpenDocument o l
+ Strikeout l -> withTextStyle Strike $ inlinesToOpenDocument o l
+ Superscript l -> withTextStyle Sup $ inlinesToOpenDocument o l
+ Subscript l -> withTextStyle Sub $ inlinesToOpenDocument o l
+ SmallCaps l -> withTextStyle SmallC $ inlinesToOpenDocument o l
+ Quoted t l -> inQuotes t <$> inlinesToOpenDocument o l
+ Code _ s -> withTextStyle Pre $ inTextStyle $ preformatted s
+ Math t s -> inlinesToOpenDocument o (texMathToInlines t s)
+ Cite _ l -> inlinesToOpenDocument o l
+ RawInline f s -> if f == Format "opendocument"
+ then return $ text s
+ else return empty
+ Link _ l (s,t) -> mkLink s t <$> inlinesToOpenDocument o l
+ Image attr _ (s,t) -> mkImg attr s t
+ Note l -> mkNote l
where
preformatted s = handleSpaces $ escapeStringForXML s
mkLink s t = inTags False "text:a" [ ("xlink:type" , "simple")
, ("xlink:href" , s )
, ("office:name", t )
] . inSpanTags "Definition"
- mkImg s t = do
+ mkImg (_, _, kvs) s _ = do
id' <- gets stImageId
modify (\st -> st{ stImageId = id' + 1 })
+ let getDims [] = []
+ getDims (("width", w) :xs) = ("svg:width", w) : getDims xs
+ getDims (("height", h):xs) = ("svg:height", h) : getDims xs
+ getDims (x@("style:rel-width", _) :xs) = x : getDims xs
+ getDims (x@("style:rel-height", _):xs) = x : getDims xs
+ getDims (_:xs) = getDims xs
return $ inTags False "draw:frame"
- (("draw:name", "img" ++ show id'):attrsFromTitle t) $
+ (("draw:name", "img" ++ show id') : getDims kvs) $
selfClosingTag "draw:image" [ ("xlink:href" , s )
, ("xlink:type" , "simple")
, ("xlink:show" , "embed" )
@@ -422,17 +431,6 @@ inlineToOpenDocument o ils
addNote nn
return nn
--- a title of the form "120x140" will be interpreted as image
--- size in points.
-attrsFromTitle :: String -> [(String,String)]
-attrsFromTitle s = if null xs || null ys
- then []
- else [("svg:width",xs ++ "pt"),("svg:height",ys ++ "pt")]
- where (xs,rest) = span isDigit s
- ys = case rest of
- ('x':zs) | all isDigit zs -> zs
- _ -> ""
-
bulletListStyle :: Int -> State WriterState (Int,(Int,[Doc]))
bulletListStyle l =
let doStyles i = inTags True "text:list-level-style-bullet"