aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/ICML.hs
diff options
context:
space:
mode:
authorJesse Rosenthal <jrosenthal@jhu.edu>2016-09-24 17:52:25 -0400
committerJohn MacFarlane <jgm@berkeley.edu>2017-01-25 17:07:39 +0100
commit32c68dada92eb142949c5be5224a3ddf20fcf484 (patch)
tree41ba1aaf202d0f6093218ab1ceadaf3b159c5a83 /src/Text/Pandoc/Writers/ICML.hs
parent0ab4af2f03f4226714a39c959c161def679d9d57 (diff)
downloadpandoc-32c68dada92eb142949c5be5224a3ddf20fcf484.tar.gz
Introduce pure versions of IO Writers.
Using Text.Pandoc.Free, introduce pure versions of Docx, EPUB, ICML, and ODT writers. Each of the pure versions is exported along with the IO version (produced by running `runIO` on the pure reader). Ideally, this should make the writers easier to test.
Diffstat (limited to 'src/Text/Pandoc/Writers/ICML.hs')
-rw-r--r--src/Text/Pandoc/Writers/ICML.hs19
1 files changed, 13 insertions, 6 deletions
diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs
index e2c123fc2..3a1e772ce 100644
--- a/src/Text/Pandoc/Writers/ICML.hs
+++ b/src/Text/Pandoc/Writers/ICML.hs
@@ -18,7 +18,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.XML
import Text.Pandoc.Readers.TeXMath (texMathToInlines)
import Text.Pandoc.Writers.Shared
-import Text.Pandoc.Shared (linesToPara, splitBy, fetchItem, warn)
+import Text.Pandoc.Shared (linesToPara, splitBy, warn)
import Text.Pandoc.Options
import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Pretty
@@ -28,6 +28,10 @@ import Data.Text as Text (breakOnAll, pack)
import Control.Monad.State
import Network.URI (isURI)
import qualified Data.Set as Set
+import Text.Pandoc.Free (runIO)
+import qualified Text.Pandoc.Free as P
+
+type ICMLAction = P.PandocAction ()
type Style = [String]
type Hyperlink = [(Int, String)]
@@ -40,7 +44,7 @@ data WriterState = WriterState{
, maxListDepth :: Int
}
-type WS a = StateT WriterState IO a
+type WS a = StateT WriterState ICMLAction a
defaultWriterState :: WriterState
defaultWriterState = WriterState{
@@ -121,10 +125,13 @@ subListParName = "subParagraph"
footnoteName = "Footnote"
citeName = "Cite"
-
-- | Convert Pandoc document to string in ICML format.
writeICML :: WriterOptions -> Pandoc -> IO String
-writeICML opts (Pandoc meta blocks) = do
+writeICML opts doc = runIO $ writeICMLPure opts doc
+
+-- | Convert Pandoc document to string in ICML format.
+writeICMLPure :: WriterOptions -> Pandoc -> ICMLAction String
+writeICMLPure opts (Pandoc meta blocks) = do
let colwidth = if writerWrapText opts == WrapAuto
then Just $ writerColumns opts
else Nothing
@@ -532,10 +539,10 @@ styleToStrAttr style =
-- | Assemble an ICML Image.
imageICML :: WriterOptions -> Style -> Attr -> Target -> WS Doc
imageICML opts style attr (src, _) = do
- res <- liftIO $ fetchItem (writerSourceURL opts) src
+ res <- lift $ P.fetchItem (writerSourceURL opts) src
imgS <- case res of
Left (_) -> do
- warn $ "Could not find image `" ++ src ++ "', skipping..."
+ lift $ P.warn $ "Could not find image `" ++ src ++ "', skipping..."
return def
Right (img, _) -> do
case imageSize img of