aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Texinfo.hs
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2015-11-19 22:41:12 -0800
committerJohn MacFarlane <jgm@berkeley.edu>2015-11-19 23:14:23 -0800
commit244cd5644b44f43722530379138bd7bb9cbace9b (patch)
tree771cf6688ca92dc054616318372e6759fb594587 /src/Text/Pandoc/Writers/Texinfo.hs
parent1ad296dc69d0e901ce26d446b57758feea5a52c6 (diff)
parent08243d53a68239fe60fdcb59ee71f6562b16f5c7 (diff)
downloadpandoc-244cd5644b44f43722530379138bd7bb9cbace9b.tar.gz
Merge branch 'new-image-attributes' of https://github.com/mb21/pandoc into mb21-new-image-attributes
* Bumped version to 1.16. * Added Attr field to Link and Image. * Added `common_link_attributes` extension. * Updated readers for link attributes. * Updated writers for link attributes. * Updated tests * Updated stack.yaml to build against unreleased versions of pandoc-types and texmath. * Fixed various compiler warnings. Closes #261. TODO: * Relative (percentage) image widths in docx writer. * ODT/OpenDocument writer (untested, same issue about percentage widths). * Update pandoc-citeproc.
Diffstat (limited to 'src/Text/Pandoc/Writers/Texinfo.hs')
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs25
1 files changed, 17 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index 2325d1425..cd9e2ef3d 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -40,6 +40,7 @@ import Data.Ord ( comparing )
import Data.Char ( chr, ord )
import Control.Monad.State
import Text.Pandoc.Pretty
+import Text.Pandoc.ImageSize
import Network.URI ( isURI, unEscapeString )
import System.FilePath
@@ -49,6 +50,7 @@ data WriterState =
, stSubscript :: Bool -- document contains subscript
, stEscapeComma :: Bool -- in a context where we need @comma
, stIdentifiers :: [String] -- header ids used already
+ , stOptions :: WriterOptions -- writer options
}
{- TODO:
@@ -61,7 +63,8 @@ writeTexinfo :: WriterOptions -> Pandoc -> String
writeTexinfo options document =
evalState (pandocToTexinfo options $ wrapTop document) $
WriterState { stStrikeout = False, stSuperscript = False,
- stEscapeComma = False, stSubscript = False, stIdentifiers = [] }
+ stEscapeComma = False, stSubscript = False,
+ stIdentifiers = [], stOptions = options}
-- | Add a "Top" node around the document, needed by Texinfo.
wrapTop :: Pandoc -> Pandoc
@@ -130,12 +133,12 @@ blockToTexinfo (Plain lst) =
inlineListToTexinfo lst
-- title beginning with fig: indicates that the image is a figure
-blockToTexinfo (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
+blockToTexinfo (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
capt <- if null txt
then return empty
else (\c -> text "@caption" <> braces c) `fmap`
inlineListToTexinfo txt
- img <- inlineToTexinfo (Image txt (src,tit))
+ img <- inlineToTexinfo (Image attr txt (src,tit))
return $ text "@float" $$ img $$ capt $$ text "@end float"
blockToTexinfo (Para lst) =
@@ -424,11 +427,11 @@ inlineToTexinfo (RawInline f str)
inlineToTexinfo (LineBreak) = return $ text "@*" <> cr
inlineToTexinfo Space = return space
-inlineToTexinfo (Link txt (src@('#':_), _)) = do
+inlineToTexinfo (Link _ txt (src@('#':_), _)) = do
contents <- escapeCommas $ inlineListToTexinfo txt
return $ text "@ref" <>
braces (text (stringToTexinfo src) <> text "," <> contents)
-inlineToTexinfo (Link txt (src, _)) = do
+inlineToTexinfo (Link _ txt (src, _)) = do
case txt of
[Str x] | escapeURI x == src -> -- autolink
do return $ text $ "@url{" ++ x ++ "}"
@@ -437,10 +440,16 @@ inlineToTexinfo (Link txt (src, _)) = do
return $ text ("@uref{" ++ src1 ++ ",") <> contents <>
char '}'
-inlineToTexinfo (Image alternate (source, _)) = do
+inlineToTexinfo (Image attr alternate (source, _)) = do
content <- escapeCommas $ inlineListToTexinfo alternate
- return $ text ("@image{" ++ base ++ ",,,") <> content <> text "," <>
- text (ext ++ "}")
+ opts <- gets stOptions
+ let showDim dim = case (dimension dim attr) of
+ (Just (Pixel a)) -> showInInch opts (Pixel a) ++ "in"
+ (Just (Percent _)) -> ""
+ (Just d) -> show d
+ Nothing -> ""
+ return $ text ("@image{" ++ base ++ ',':(showDim Width) ++ ',':(showDim Height) ++ ",")
+ <> content <> text "," <> text (ext ++ "}")
where
ext = drop 1 $ takeExtension source'
base = dropExtension source'