diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Text/Pandoc/Readers/EPUB.hs | 9 | ||||
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/Docx.hs | 8 | ||||
-rw-r--r-- | src/Text/Pandoc/Writers/RST.hs | 9 |
4 files changed, 12 insertions, 15 deletions
diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs index 338540533..aefc32e0e 100644 --- a/src/Text/Pandoc/Readers/EPUB.hs +++ b/src/Text/Pandoc/Readers/EPUB.hs @@ -181,7 +181,6 @@ getManifest archive = do fixInternalReferences :: FilePath -> Pandoc -> Pandoc fixInternalReferences pathToFile = (walk $ renameImages root) - . (walk normalisePath) . (walk $ fixBlockIRs filename) . (walk $ fixInlineIRs filename) where @@ -196,12 +195,6 @@ fixInlineIRs s (Link t ('#':url, tit)) = Link t (addHash s url, tit) fixInlineIRs _ v = v -normalisePath :: Inline -> Inline -normalisePath (Link t (url, tit)) = - let (path, uid) = span (/= '#') url in - Link t (takeFileName path ++ uid, tit) -normalisePath s = s - prependHash :: [String] -> Inline -> Inline prependHash ps l@(Link is (url, tit)) | or [s `isPrefixOf` url | s <- ps] = @@ -223,7 +216,7 @@ fixAttrs s (ident, cs, kvs) = (addHash s ident, filter (not . null) cs, removeEP addHash :: String -> String -> String addHash _ "" = "" -addHash s ident = s ++ "#" ++ ident +addHash s ident = takeFileName s ++ "#" ++ ident removeEPUBAttrs :: [(String, String)] -> [(String, String)] removeEPUBAttrs kvs = filter (not . isEPUBAttr) kvs diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 07a7e962c..c44133e12 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -540,6 +540,7 @@ stringify = query go . walk deNote go (Str x) = x go (Code _ x) = x go (Math _ x) = x + go (RawInline (Format "html") ('<':'b':'r':_)) = " " -- see #2105 go LineBreak = " " go _ = "" deNote (Note _) = Str "" diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index da4c78cef..0cb313e7b 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -181,8 +181,8 @@ renumIds f renumMap = map (renumId f renumMap) -- | Certain characters are invalid in XML even if escaped. -- See #1992 -stripInvalidChars :: Pandoc -> Pandoc -stripInvalidChars = bottomUp (filter isValidChar) +stripInvalidChars :: String -> String +stripInvalidChars = filter isValidChar -- | See XML reference isValidChar :: Char -> Bool @@ -208,7 +208,7 @@ writeDocx :: WriterOptions -- ^ Writer options -> IO BL.ByteString writeDocx opts doc@(Pandoc meta _) = do let datadir = writerUserDataDir opts - let doc' = stripInvalidChars . walk fixDisplayMath $ doc + let doc' = walk fixDisplayMath $ doc username <- lookup "USERNAME" <$> getEnvironment utctime <- getCurrentTime distArchive <- getDefaultReferenceDocx Nothing @@ -974,7 +974,7 @@ formattedString str = do return [ mknode "w:r" [] $ props ++ [ mknode (if inDel then "w:delText" else "w:t") - [("xml:space","preserve")] str ] ] + [("xml:space","preserve")] (stripInvalidChars str) ] ] setFirstPara :: WS () setFirstPara = modify $ \s -> s { stFirstPara = True } diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 151d3c2ae..fae908f30 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -333,7 +333,8 @@ blockListToRST = blockListToRST' False -- | Convert list of Pandoc inline elements to RST. inlineListToRST :: [Inline] -> State WriterState Doc inlineListToRST lst = - mapM inlineToRST (removeSpaceAfterDisplayMath $ insertBS lst) >>= return . hcat + mapM inlineToRST (removeSpaceAfterDisplayMath $ insertBS lst) >>= + return . hcat where -- remove spaces after displaymath, as they screw up indentation: removeSpaceAfterDisplayMath (Math DisplayMath x : zs) = Math DisplayMath x : dropWhile (==Space) zs @@ -341,8 +342,8 @@ inlineListToRST lst = removeSpaceAfterDisplayMath [] = [] insertBS :: [Inline] -> [Inline] -- insert '\ ' where needed insertBS (x:y:z:zs) - | isComplex y && surroundComplex x z = - x : y : RawInline "rst" "\\ " : insertBS (z:zs) + | isComplex y && (surroundComplex x z) = + x : y : insertBS (z : zs) insertBS (x:y:zs) | isComplex x && not (okAfterComplex y) = x : RawInline "rst" "\\ " : insertBS (y : zs) @@ -383,6 +384,8 @@ inlineListToRST lst = isComplex (Image _ _) = True isComplex (Code _ _) = True isComplex (Math _ _) = True + isComplex (Cite _ (x:_)) = isComplex x + isComplex (Span _ (x:_)) = isComplex x isComplex _ = False -- | Convert Pandoc inline element to RST. |