aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/OpenDocument.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <fiddlosopher@gmail.com>2012-01-14 11:39:20 -0800
committerJohn MacFarlane <fiddlosopher@gmail.com>2012-01-14 11:39:20 -0800
commit0299ae6c29e59674370dab884179045fef6b51f0 (patch)
treefb8fc944f8ff5ed1eb6ccb41b2fafa1b00f0cd4b /src/Text/Pandoc/Writers/OpenDocument.hs
parentd0582b912b160512c5a4f1737d544c7e9a3b3fed (diff)
downloadpandoc-0299ae6c29e59674370dab884179045fef6b51f0.tar.gz
OpenDocument writer: treat image title of form "dddxddd" as size in px.
Later we'll modify the ODT writer to insert such titles, so image sizes will be correct in the ODT.
Diffstat (limited to 'src/Text/Pandoc/Writers/OpenDocument.hs')
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs17
1 files changed, 14 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index 23ef2e31d..1153aab6a 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -40,7 +40,7 @@ import Text.Printf ( printf )
import Control.Applicative ( (<$>) )
import Control.Arrow ( (***), (>>>) )
import Control.Monad.State hiding ( when )
-import Data.Char (chr)
+import Data.Char (chr, isDigit)
import qualified Data.Map as Map
-- | Auxiliary function to convert Plain block to Para.
@@ -378,7 +378,7 @@ inlineToOpenDocument o ils
| RawInline "html" s <- ils = preformatted s -- for backwards compat.
| RawInline _ _ <- ils = return empty
| Link l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l
- | Image _ (s,_) <- ils = return $ mkImg s
+ | Image _ (s,t) <- ils = return $ mkImg s t
| Note l <- ils = mkNote l
| otherwise = return empty
where
@@ -387,7 +387,7 @@ inlineToOpenDocument o ils
, ("xlink:href" , s )
, ("office:name", t )
] . inSpanTags "Definition"
- mkImg s = inTags False "draw:frame" [] $
+ mkImg s t = inTags False "draw:frame" (attrsFromTitle t) $
selfClosingTag "draw:image" [ ("xlink:href" , s )
, ("xlink:type" , "simple")
, ("xlink:show" , "embed" )
@@ -403,6 +403,17 @@ inlineToOpenDocument o ils
addNote nn
return nn
+-- a title of the form "120x140" will be interpreted as image
+-- size in pixels.
+attrsFromTitle :: String -> [(String,String)]
+attrsFromTitle s = if null xs || null ys
+ then []
+ else [("svg:x",xs),("svg:y",ys)]
+ 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"