aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
m---------data/templates12
-rw-r--r--pandoc.hs15
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs13
3 files changed, 24 insertions, 16 deletions
diff --git a/data/templates b/data/templates
-Subproject 950b54c55c5e6577a09715d9654abafac445ab5
+Subproject ecb769cb7b4354234135c030dcb03a064f03947
diff --git a/pandoc.hs b/pandoc.hs
index c2d4ca853..d3fc3a1f5 100644
--- a/pandoc.hs
+++ b/pandoc.hs
@@ -44,7 +44,7 @@ import Text.Pandoc.SelfContained ( makeSelfContained )
import Text.Pandoc.Process (pipeProcess)
import Text.Highlighting.Kate ( languages, Style, tango, pygments,
espresso, zenburn, kate, haddock, monochrome )
-import System.Environment ( getArgs, getProgName, getEnvironment )
+import System.Environment ( getArgs, getProgName )
import System.Exit ( exitWith, ExitCode (..) )
import System.FilePath
import System.Console.GetOpt
@@ -113,12 +113,15 @@ isTextFormat s = takeWhile (`notElem` "+-") s `notElem` binaries
externalFilter :: FilePath -> [String] -> Pandoc -> IO Pandoc
externalFilter f args' d = do
- mbPath <- lookup "PATH" <$> getEnvironment
- mbexe <- if '/' `elem` f || mbPath == Nothing
- -- don't check PATH if filter name has a path, or
- -- if the PATH is not set
+ mbexe <- if '/' `elem` f
+ -- don't check PATH if filter name has a path
then return Nothing
- else findExecutable f
+ -- we catch isDoesNotExistError because this will
+ -- be triggered if PATH not set:
+ else E.catch (findExecutable f)
+ (\e -> if isDoesNotExistError e
+ then return Nothing
+ else throwIO e)
(f', args'') <- case mbexe of
Just x -> return (x, args')
Nothing -> do
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 38031b7dc..2ee7bd5a5 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -114,7 +114,13 @@ type WS a = StateT WriterState IO a
mknode :: Node t => String -> [(String,String)] -> t -> Element
mknode s attrs =
- add_attrs (map (\(k,v) -> Attr (unqual k) v) attrs) . node (unqual s)
+ add_attrs (map (\(k,v) -> Attr (nodename k) v) attrs) . node (nodename s)
+
+nodename :: String -> QName
+nodename s = QName{ qName = name, qURI = Nothing, qPrefix = prefix }
+ where (name, prefix) = case break (==':') s of
+ (xs,[]) -> (xs, Nothing)
+ (ys,(_:zs)) -> (zs, Just ys)
toLazy :: B.ByteString -> BL.ByteString
toLazy = BL.fromChunks . (:[])
@@ -297,7 +303,8 @@ writeDocx opts doc@(Pandoc meta _) = do
-- otherwise things break:
[Elem e | e <- allElts
, qName (elName e) == "abstractNum" ] ++
- [Elem e | e <- allElts, qName (elName e) == "num" ] }
+ [Elem e | e <- allElts
+ , qName (elName e) == "num" ] }
let docPropsPath = "docProps/core.xml"
let docProps = mknode "cp:coreProperties"
[("xmlns:cp","http://schemas.openxmlformats.org/package/2006/metadata/core-properties")
@@ -470,7 +477,7 @@ mkLvl marker lvl =
patternFor _ s = s ++ "."
getNumId :: WS Int
-getNumId = ((999 +) . length) `fmap` gets stLists
+getNumId = (((baseListId - 1) +) . length) `fmap` gets stLists
-- | Convert Pandoc document to two lists of
-- OpenXML elements (the main document and footnotes).