aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/ICML.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/ICML.hs')
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs14
1 files changed, 8 insertions, 6 deletions
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index ae20efd4b..6af4b7aa3 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -1,4 +1,4 @@
-{-# LANGUAGE OverloadedStrings #-}
+{-# LANGUAGE OverloadedStrings, FlexibleContexts #-}
{- |
Module : Text.Pandoc.Writers.ICML
@@ -70,7 +70,6 @@ linkName = "Link"
-- block element names (appear in InDesign's paragraph styles pane)
paragraphName :: String
codeBlockName :: String
-rawBlockName :: String
blockQuoteName :: String
orderedListName :: String
bulletListName :: String
@@ -93,7 +92,6 @@ subListParName :: String
footnoteName :: String
paragraphName = "Paragraph"
codeBlockName = "CodeBlock"
-rawBlockName = "Rawblock"
blockQuoteName = "Blockquote"
orderedListName = "NumList"
bulletListName = "BulList"
@@ -278,7 +276,9 @@ blockToICML :: WriterOptions -> Style -> Block -> WS Doc
blockToICML opts style (Plain lst) = parStyle opts style lst
blockToICML opts style (Para lst) = parStyle opts (paragraphName:style) lst
blockToICML opts style (CodeBlock _ str) = parStyle opts (codeBlockName:style) $ [Str str]
-blockToICML opts style (RawBlock _ str) = parStyle opts (rawBlockName:style) $ [Str str]
+blockToICML _ _ (RawBlock f str)
+ | f == Format "icml" = return $ text str
+ | otherwise = return empty
blockToICML opts style (BlockQuote blocks) = blocksToICML opts (blockQuoteName:style) blocks
blockToICML opts style (OrderedList attribs lst) = listItemsToICML opts orderedListName style (Just attribs) lst
blockToICML opts style (BulletList lst) = listItemsToICML opts bulletListName style Nothing lst
@@ -399,12 +399,14 @@ inlineToICML opts style (Subscript lst) = inlinesToICML opts (subscriptName:styl
inlineToICML opts style (SmallCaps lst) = inlinesToICML opts (smallCapsName:style) lst
inlineToICML opts style (Quoted SingleQuote lst) = inlinesToICML opts style $ [Str "‘"] ++ lst ++ [Str "’"]
inlineToICML opts style (Quoted DoubleQuote lst) = inlinesToICML opts style $ [Str "“"] ++ lst ++ [Str "”"]
-inlineToICML opts style (Cite _ lst) = footnoteToICML opts style [Para lst]
+inlineToICML opts style (Cite _ lst) = inlinesToICML opts style lst
inlineToICML _ style (Code _ str) = charStyle (codeName:style) $ text $ escapeStringForXML str
inlineToICML _ style Space = charStyle style space
inlineToICML _ style LineBreak = charStyle style $ text lineSeparator
inlineToICML _ style (Math _ str) = charStyle style $ text $ escapeStringForXML str --InDesign doesn't really do math
-inlineToICML _ style (RawInline _ str) = charStyle style $ text $ escapeStringForXML str
+inlineToICML _ _ (RawInline f str)
+ | f == Format "icml" = return $ text str
+ | otherwise = return empty
inlineToICML opts style (Link lst (url, title)) = do
content <- inlinesToICML opts (linkName:style) lst
state $ \st ->