Docx line breaks: Use w:cr in w:r instead of w:br.

This seems to fix a problem viewing pandoc-generated
docx files in LibreOffice.
This commit is contained in:
John MacFarlane 2012-08-17 18:27:48 -07:00
parent c7bd034fa8
commit fd616665ac

View file

@ -543,7 +543,7 @@ inlineToOpenXML opts (SmallCaps lst) =
inlineToOpenXML opts (Strikeout lst) = inlineToOpenXML opts (Strikeout lst) =
withTextProp (mknode "w:strike" [] ()) withTextProp (mknode "w:strike" [] ())
$ inlinesToOpenXML opts lst $ inlinesToOpenXML opts lst
inlineToOpenXML _ LineBreak = return [ mknode "w:br" [] () ] inlineToOpenXML _ LineBreak = return [br]
inlineToOpenXML _ (RawInline f str) inlineToOpenXML _ (RawInline f str)
| f == "openxml" = return [ x | Elem x <- parseXML str ] | f == "openxml" = return [ x | Elem x <- parseXML str ]
| otherwise = return [] | otherwise = return []
@ -562,16 +562,14 @@ inlineToOpenXML opts (Math DisplayMath str) =
Left _ -> do Left _ -> do
fallback <- inlinesToOpenXML opts (readTeXMath str) fallback <- inlinesToOpenXML opts (readTeXMath str)
return $ [br] ++ fallback ++ [br] return $ [br] ++ fallback ++ [br]
where br = mknode "w:br" [] ()
inlineToOpenXML opts (Cite _ lst) = inlinesToOpenXML opts lst inlineToOpenXML opts (Cite _ lst) = inlinesToOpenXML opts lst
inlineToOpenXML _ (Code attrs str) = inlineToOpenXML _ (Code attrs str) =
withTextProp (rStyle "VerbatimChar") withTextProp (rStyle "VerbatimChar")
$ case highlight formatOpenXML attrs str of $ case highlight formatOpenXML attrs str of
Nothing -> intercalate [mknode "w:br" [] ()] Nothing -> intercalate [br]
`fmap` (mapM formattedString $ lines str) `fmap` (mapM formattedString $ lines str)
Just h -> return h Just h -> return h
where formatOpenXML _fmtOpts = intercalate [mknode "w:br" [] ()] . where formatOpenXML _fmtOpts = intercalate [br] . map (map toHlTok)
map (map toHlTok)
toHlTok (toktype,tok) = mknode "w:r" [] toHlTok (toktype,tok) = mknode "w:r" []
[ mknode "w:rPr" [] [ mknode "w:rPr" []
[ rStyle $ show toktype ] [ rStyle $ show toktype ]
@ -669,3 +667,6 @@ inlineToOpenXML opts (Image alt (src, tit)) = do
liftIO $ UTF8.hPutStrLn stderr $ liftIO $ UTF8.hPutStrLn stderr $
"Could not find image `" ++ src ++ "', skipping..." "Could not find image `" ++ src ++ "', skipping..."
inlinesToOpenXML opts alt inlinesToOpenXML opts alt
br :: Element
br = mknode "w:r" [] [mknode "w:cr" [] () ]