aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc')
-rw-r--r--src/Text/Pandoc/Readers/Docx/Parse.hs10
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs10
-rw-r--r--src/Text/Pandoc/Writers/Custom.hs16
-rw-r--r--src/Text/Pandoc/Writers/EPUB.hs29
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs3
5 files changed, 53 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs
index 5fd6b7a81..671d2acf3 100644
--- a/src/Text/Pandoc/Readers/Docx/Parse.hs
+++ b/src/Text/Pandoc/Readers/Docx/Parse.hs
@@ -639,6 +639,16 @@ elemToParPart ns element
case drawing of
Just s -> expandDrawingId s >>= (\(fp, bs) -> return $ Drawing fp bs)
Nothing -> throwError WrongElem
+-- The below is an attempt to deal with images in deprecated vml format.
+elemToParPart ns element
+ | isElem ns "w" "r" element
+ , Just _ <- findChild (elemName ns "w" "pict") element =
+ let drawing = findElement (elemName ns "v" "imagedata") element
+ >>= findAttr (elemName ns "r" "id")
+ in
+ case drawing of
+ Just s -> expandDrawingId s >>= (\(fp, bs) -> return $ Drawing fp bs)
+ Nothing -> throwError WrongElem
elemToParPart ns element
| isElem ns "w" "r" element =
elemToRun ns element >>= (\r -> return $ PlainRun r)
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 6f3090e10..942b9f3b3 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -898,6 +898,12 @@ backslash' = string "\\"
braced' :: IncludeParser
braced' = try $ char '{' *> manyTill (satisfy (/='}')) (char '}')
+maybeAddExtension :: String -> FilePath -> FilePath
+maybeAddExtension ext fp =
+ if null (takeExtension fp)
+ then addExtension fp ext
+ else fp
+
include' :: IncludeParser
include' = do
fs' <- try $ do
@@ -909,8 +915,8 @@ include' = do
skipMany $ try $ char '[' *> (manyTill anyChar (char ']'))
fs <- (map trim . splitBy (==',')) <$> braced'
return $ if name == "usepackage"
- then map (flip replaceExtension ".sty") fs
- else map (flip replaceExtension ".tex") fs
+ then map (maybeAddExtension ".sty") fs
+ else map (maybeAddExtension ".tex") fs
pos <- getPosition
containers <- getState
let fn = case containers of
diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs
index 914d61850..6fc3b9b3c 100644
--- a/src/Text/Pandoc/Writers/Custom.hs
+++ b/src/Text/Pandoc/Writers/Custom.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE OverlappingInstances, FlexibleInstances, OverloadedStrings,
- ScopedTypeVariables #-}
+ ScopedTypeVariables, DeriveDataTypeable #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{- Copyright (C) 2012-2014 John MacFarlane <jgm@berkeley.edu>
@@ -35,6 +35,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Options
import Data.List ( intersperse )
import Data.Char ( toLower )
+import Data.Typeable
import Scripting.Lua (LuaState, StackValue, callfunc)
import Text.Pandoc.Writers.Shared
import qualified Scripting.Lua as Lua
@@ -42,6 +43,8 @@ import Text.Pandoc.UTF8 (fromString, toString)
import Data.ByteString (ByteString)
import qualified Data.ByteString.Char8 as C8
import Data.Monoid
+import Control.Monad (when)
+import Control.Exception
import qualified Data.Map as M
import Text.Pandoc.Templates
@@ -145,13 +148,22 @@ instance StackValue Citation where
peek = undefined
valuetype _ = Lua.TTABLE
+data PandocLuaException = PandocLuaException String
+ deriving (Show, Typeable)
+
+instance Exception PandocLuaException
+
-- | Convert Pandoc to custom markup.
writeCustom :: FilePath -> WriterOptions -> Pandoc -> IO String
writeCustom luaFile opts doc@(Pandoc meta _) = do
luaScript <- C8.unpack `fmap` C8.readFile luaFile
lua <- Lua.newstate
Lua.openlibs lua
- Lua.loadstring lua luaScript "custom"
+ status <- Lua.loadstring lua luaScript luaFile
+ -- check for error in lua script (later we'll change the return type
+ -- to handle this more gracefully):
+ when (status /= 0) $
+ Lua.tostring lua 1 >>= throw . PandocLuaException
Lua.call lua 0 0
-- TODO - call hierarchicalize, so we have that info
rendered <- docToCustom lua opts doc
diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs
index 212206ac6..cebbaa835 100644
--- a/src/Text/Pandoc/Writers/EPUB.hs
+++ b/src/Text/Pandoc/Writers/EPUB.hs
@@ -41,7 +41,7 @@ import qualified Data.ByteString.Lazy.Char8 as B8
import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.SelfContained ( makeSelfContained )
import Codec.Archive.Zip ( emptyArchive, addEntryToArchive, eRelativePath, fromEntry , Entry, toEntry, fromArchive)
-import Control.Applicative ((<$>))
+import Control.Applicative ((<$>), (<$))
import Data.Time.Clock.POSIX ( getPOSIXTime )
import Data.Time (getCurrentTime,UTCTime, formatTime)
import Text.Pandoc.Compat.Locale ( defaultTimeLocale )
@@ -57,7 +57,7 @@ import Text.Pandoc.Options ( WriterOptions(..)
import Text.Pandoc.Definition
import Text.Pandoc.Walk (walk, walkM)
import Control.Monad.State (modify, get, execState, State, put, evalState)
-import Control.Monad (foldM, when, mplus, liftM)
+import Control.Monad (foldM, mplus, liftM)
import Text.XML.Light ( unode, Element(..), unqual, Attr(..), add_attrs
, strContent, lookupAttr, Node(..), QName(..), parseXML
, onlyElems, node, ppElement)
@@ -894,20 +894,27 @@ addIdentifiers bs = evalState (mapM go bs) []
-- was "header-1" might turn into "ch006.xhtml#header".
correlateRefs :: Int -> [Block] -> [(String,String)]
correlateRefs chapterHeaderLevel bs =
- identTable $ execState (mapM_ go bs)
+ identTable $ execState (walkM goBlock bs >>= walkM goInline)
IdentState{ chapterNumber = 0
, identTable = [] }
- where go :: Block -> State IdentState ()
- go (Header n (ident,_,_) _) = do
- when (n <= chapterHeaderLevel) $
- modify $ \s -> s{ chapterNumber = chapterNumber s + 1 }
+ where goBlock :: Block -> State IdentState Block
+ goBlock x@(Header n (ident,_,_) _) = x <$ addIdentifier (Just n) ident
+ goBlock x@(Div (ident,_,_) _) = x <$ addIdentifier Nothing ident
+ goBlock x = return x
+ goInline :: Inline -> State IdentState Inline
+ goInline x@(Span (ident,_,_) _) = x <$ addIdentifier Nothing ident
+ goInline x = return x
+ addIdentifier mbHeaderLevel ident = do
+ case mbHeaderLevel of
+ Just n | n <= chapterHeaderLevel ->
+ modify $ \s -> s{ chapterNumber = chapterNumber s + 1 }
+ _ -> return ()
st <- get
let chapterid = showChapter (chapterNumber st) ++
- if n <= chapterHeaderLevel
- then ""
- else '#' : ident
+ case mbHeaderLevel of
+ Just n | n <= chapterHeaderLevel -> ""
+ _ -> '#' : ident
modify $ \s -> s{ identTable = (ident, chapterid) : identTable st }
- go _ = return ()
-- Replace internal link references using the table produced
-- by correlateRefs.
diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 46974930e..b3a2d264d 100644
--- a/src/Text/Pandoc/Writers/HTML.hs
+++ b/src/Text/Pandoc/Writers/HTML.hs
@@ -49,7 +49,10 @@ import Data.String ( fromString )
import Data.Maybe ( catMaybes, fromMaybe )
import Control.Monad.State
import Text.Blaze.Html hiding(contents)
+#if MIN_VERSION_blaze_markup(0,6,3)
+#else
import Text.Blaze.Internal(preEscapedString)
+#endif
#if MIN_VERSION_blaze_html(0,5,1)
import qualified Text.Blaze.XHtml5 as H5
#else