ICML writer: changed type of writeICML.

API change:  It is now `WriterOptions -> Pandoc -> IO String`.

Also handle new image attributes.

(mb21)
This commit is contained in:
John MacFarlane 2015-04-02 21:06:51 -07:00 committed by mb21
parent 4391c5f34c
commit 9deb335ca5
2 changed files with 51 additions and 40 deletions

View file

@ -273,7 +273,7 @@ writers = [
,("html" , PureStringWriter writeHtmlString) ,("html" , PureStringWriter writeHtmlString)
,("html5" , PureStringWriter $ \o -> ,("html5" , PureStringWriter $ \o ->
writeHtmlString o{ writerHtml5 = True }) writeHtmlString o{ writerHtml5 = True })
,("icml" , PureStringWriter writeICML) ,("icml" , IOStringWriter writeICML)
,("s5" , PureStringWriter $ \o -> ,("s5" , PureStringWriter $ \o ->
writeHtmlString o{ writerSlideVariant = S5Slides writeHtmlString o{ writerSlideVariant = S5Slides
, writerTableOfContents = False }) , writerTableOfContents = False })

View file

@ -17,15 +17,17 @@ module Text.Pandoc.Writers.ICML (writeICML) where
import Text.Pandoc.Definition import Text.Pandoc.Definition
import Text.Pandoc.XML import Text.Pandoc.XML
import Text.Pandoc.Writers.Shared import Text.Pandoc.Writers.Shared
import Text.Pandoc.Shared (splitBy) import Text.Pandoc.Shared (splitBy, fetchItem, warn)
import Text.Pandoc.Options import Text.Pandoc.Options
import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Pretty import Text.Pandoc.Pretty
import Text.Pandoc.ImageSize
import Data.List (isPrefixOf, isInfixOf, stripPrefix) import Data.List (isPrefixOf, isInfixOf, stripPrefix)
import Data.Text as Text (breakOnAll, pack) import Data.Text as Text (breakOnAll, pack)
import Data.Monoid (mappend) import Data.Monoid (mappend)
import Control.Monad.State import Control.Monad.State
import Network.URI (isURI) import Network.URI (isURI)
import System.FilePath (pathSeparator)
import qualified Data.Set as Set import qualified Data.Set as Set
type Style = [String] type Style = [String]
@ -39,7 +41,7 @@ data WriterState = WriterState{
, maxListDepth :: Int , maxListDepth :: Int
} }
type WS a = State WriterState a type WS a = StateT WriterState IO a
defaultWriterState :: WriterState defaultWriterState :: WriterState
defaultWriterState = WriterState{ defaultWriterState = WriterState{
@ -118,27 +120,27 @@ citeName = "Cite"
-- | Convert Pandoc document to string in ICML format. -- | Convert Pandoc document to string in ICML format.
writeICML :: WriterOptions -> Pandoc -> String writeICML :: WriterOptions -> Pandoc -> IO String
writeICML opts (Pandoc meta blocks) = writeICML opts (Pandoc meta blocks) = do
let colwidth = if writerWrapText opts let colwidth = if writerWrapText opts
then Just $ writerColumns opts then Just $ writerColumns opts
else Nothing else Nothing
render' = render colwidth render' = render colwidth
renderMeta f s = Just $ render' $ fst $ runState (f opts [] s) defaultWriterState renderMeta f s = liftM (render' . fst) $ runStateT (f opts [] s) defaultWriterState
Just metadata = metaToJSON opts metadata <- metaToJSON opts
(renderMeta blocksToICML) (renderMeta blocksToICML)
(renderMeta inlinesToICML) (renderMeta inlinesToICML)
meta meta
(doc, st) = runState (blocksToICML opts [] blocks) defaultWriterState (doc, st) <- runStateT (blocksToICML opts [] blocks) defaultWriterState
main = render' doc let main = render' doc
context = defField "body" main context = defField "body" main
$ defField "charStyles" (render' $ charStylesToDoc st) $ defField "charStyles" (render' $ charStylesToDoc st)
$ defField "parStyles" (render' $ parStylesToDoc st) $ defField "parStyles" (render' $ parStylesToDoc st)
$ defField "hyperlinks" (render' $ hyperlinksToDoc $ links st) $ defField "hyperlinks" (render' $ hyperlinksToDoc $ links st)
$ metadata $ metadata
in if writerStandalone opts return $ if writerStandalone opts
then renderTemplate' (writerTemplate opts) context then renderTemplate' (writerTemplate opts) context
else main else main
-- | Auxilary functions for parStylesToDoc and charStylesToDoc. -- | Auxilary functions for parStylesToDoc and charStylesToDoc.
contains :: String -> (String, (String, String)) -> [(String, String)] contains :: String -> (String, (String, String)) -> [(String, String)]
@ -427,7 +429,7 @@ inlineToICML opts style (Link lst (url, title)) = do
cont = inTags True "HyperlinkTextSource" cont = inTags True "HyperlinkTextSource"
[("Self","htss-"++show ident), ("Name",title), ("Hidden","false")] content [("Self","htss-"++show ident), ("Name",title), ("Hidden","false")] content
in (cont, newst) in (cont, newst)
inlineToICML opts style (Image alt target) = imageICML opts style alt target inlineToICML opts style (Image attr alt target) = imageICML opts style attr alt target
inlineToICML opts style (Note lst) = footnoteToICML opts style lst inlineToICML opts style (Note lst) = footnoteToICML opts style lst
inlineToICML opts style (Span _ lst) = inlinesToICML opts style lst inlineToICML opts style (Span _ lst) = inlinesToICML opts style lst
@ -500,39 +502,48 @@ styleToStrAttr style =
in (stlStr, attrs) in (stlStr, attrs)
-- | Assemble an ICML Image. -- | Assemble an ICML Image.
imageICML :: WriterOptions -> Style -> [Inline] -> Target -> WS Doc imageICML :: WriterOptions -> Style -> Attr -> [Inline] -> Target -> WS Doc
imageICML _ style _ (linkURI, _) = imageICML opts style attr _ (src, _) = do
let imgWidth = 300::Int --TODO: set width, height dynamically as in Docx.hs res <- liftIO $ fetchItem (writerSourceURL opts) src
imgHeight = 200::Int imgS <- case res of
scaleFact = show (1::Double) --TODO: set scaling factor so image is scaled exactly to imgWidth x imgHeight Left (_) -> do
hw = show $ imgWidth `div` 2 liftIO $ warn $ "Could not find image `" ++ src ++ "', skipping..."
hh = show $ imgHeight `div` 2 return def
qw = show $ imgWidth `div` 4 Right (img, _) -> do
qh = show $ imgHeight `div` 4 case imageSize img of
uriPrefix = if isURI linkURI then "" else "file:" Right size -> return size
Left msg -> do
return $ warn $ "Could not determine image size in `" ++
src ++ "': " ++ msg
return def
let (ow, oh) = sizeInPoints imgS
(imgWidth, imgHeight) = desiredSizeInPoints opts attr imgS
hw = showFl $ ow / 2
hh = showFl $ oh / 2
scale = showFl (imgWidth / ow) ++ " 0 0 " ++ showFl (imgHeight / oh)
src' = if isURI src then src else "file://." ++ pathSeparator : src
(stlStr, attrs) = styleToStrAttr style (stlStr, attrs) = styleToStrAttr style
props = inTags True "Properties" [] $ inTags True "PathGeometry" [] props = inTags True "Properties" [] $ inTags True "PathGeometry" []
$ inTags True "GeometryPathType" [("PathOpen","false")] $ inTags True "GeometryPathType" [("PathOpen","false")]
$ inTags True "PathPointArray" [] $ inTags True "PathPointArray" []
$ vcat [ $ vcat [
selfClosingTag "PathPointType" [("Anchor", "-"++qw++" -"++qh), selfClosingTag "PathPointType" [("Anchor", "-"++hw++" -"++hh),
("LeftDirection", "-"++qw++" -"++qh), ("RightDirection", "-"++qw++" -"++qh)] ("LeftDirection", "-"++hw++" -"++hh), ("RightDirection", "-"++hw++" -"++hh)]
, selfClosingTag "PathPointType" [("Anchor", "-"++qw++" "++qh), , selfClosingTag "PathPointType" [("Anchor", "-"++hw++" "++hh),
("LeftDirection", "-"++qw++" "++qh), ("RightDirection", "-"++qw++" "++qh)] ("LeftDirection", "-"++hw++" "++hh), ("RightDirection", "-"++hw++" "++hh)]
, selfClosingTag "PathPointType" [("Anchor", qw++" "++qh), , selfClosingTag "PathPointType" [("Anchor", hw++" "++hh),
("LeftDirection", qw++" "++qh), ("RightDirection", qw++" "++qh)] ("LeftDirection", hw++" "++hh), ("RightDirection", hw++" "++hh)]
, selfClosingTag "PathPointType" [("Anchor", qw++" -"++qh), , selfClosingTag "PathPointType" [("Anchor", hw++" -"++hh),
("LeftDirection", qw++" -"++qh), ("RightDirection", qw++" -"++qh)] ("LeftDirection", hw++" -"++hh), ("RightDirection", hw++" -"++hh)]
] ]
image = inTags True "Image" image = inTags True "Image"
[("Self","ue6"), ("ItemTransform", scaleFact++" 0 0 "++scaleFact++" -"++qw++" -"++qh)] [("Self","ue6"), ("ItemTransform", scale++" -"++hw++" -"++hh)]
$ vcat [ $ vcat [
inTags True "Properties" [] $ inTags True "Profile" [("type","string")] $ text "$ID/Embedded" inTags True "Properties" [] $ inTags True "Profile" [("type","string")] $ text "$ID/Embedded"
$$ selfClosingTag "GraphicBounds" [("Left","0"), ("Top","0"), ("Right", hw), ("Bottom", hh)] , selfClosingTag "Link" [("Self", "ueb"), ("LinkResourceURI", src')]
, selfClosingTag "Link" [("Self", "ueb"), ("LinkResourceURI", uriPrefix++linkURI)]
] ]
doc = inTags True "CharacterStyleRange" attrs doc = inTags True "CharacterStyleRange" attrs
$ inTags True "Rectangle" [("Self","uec"), ("ItemTransform", "1 0 0 1 "++qw++" -"++qh)] $ inTags True "Rectangle" [("Self","uec"), ("StrokeWeight", "0"),
("ItemTransform", scale++" "++hw++" -"++hh)]
$ (props $$ image) $ (props $$ image)
in do state $ \st -> (doc, st{ inlineStyles = Set.insert stlStr $ inlineStyles st } )
state $ \st -> (doc, st{ inlineStyles = Set.insert stlStr $ inlineStyles st } )