From 56e4ecab20613d86a6660547ed87e7ff4b80d632 Mon Sep 17 00:00:00 2001 From: mpickering Date: Thu, 25 Sep 2014 12:19:52 +0100 Subject: MediaBag: Fixes Windows specific path problems Changes the internal representation to fix the problem. I haven't tested this on windows. Closes #1597 --- src/Text/Pandoc/MediaBag.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/MediaBag.hs b/src/Text/Pandoc/MediaBag.hs index 5921b56cf..a55d5417e 100644 --- a/src/Text/Pandoc/MediaBag.hs +++ b/src/Text/Pandoc/MediaBag.hs @@ -51,7 +51,7 @@ import System.IO (stderr) -- mime types. Note that a 'MediaBag' is a Monoid, so 'mempty' -- can be used for an empty 'MediaBag', and '<>' can be used to append -- two 'MediaBag's. -newtype MediaBag = MediaBag (M.Map String (MimeType, BL.ByteString)) +newtype MediaBag = MediaBag (M.Map [String] (MimeType, BL.ByteString)) deriving (Monoid) instance Show MediaBag where @@ -65,7 +65,7 @@ insertMedia :: FilePath -- ^ relative path and canonical name of resource -> MediaBag -> MediaBag insertMedia fp mbMime contents (MediaBag mediamap) = - MediaBag (M.insert fp (mime, contents) mediamap) + MediaBag (M.insert (splitPath fp) (mime, contents) mediamap) where mime = fromMaybe fallback mbMime fallback = case takeExtension fp of ".gz" -> getMimeTypeDef $ dropExtension fp @@ -75,14 +75,14 @@ insertMedia fp mbMime contents (MediaBag mediamap) = lookupMedia :: FilePath -> MediaBag -> Maybe (MimeType, BL.ByteString) -lookupMedia fp (MediaBag mediamap) = M.lookup fp mediamap +lookupMedia fp (MediaBag mediamap) = M.lookup (splitPath fp) mediamap -- | Get a list of the file paths stored in a 'MediaBag', with -- their corresponding mime types and the lengths in bytes of the contents. mediaDirectory :: MediaBag -> [(String, MimeType, Int)] mediaDirectory (MediaBag mediamap) = M.foldWithKey (\fp (mime,contents) -> - ((fp, mime, fromIntegral $ BL.length contents):)) [] mediamap + (((joinPath fp), mime, fromIntegral $ BL.length contents):)) [] mediamap -- | Extract contents of MediaBag to a given directory. Print informational -- messages if 'verbose' is true. @@ -93,7 +93,7 @@ extractMediaBag :: Bool extractMediaBag verbose dir (MediaBag mediamap) = do sequence_ $ M.foldWithKey (\fp (_ ,contents) -> - ((writeMedia verbose dir (fp, contents)):)) [] mediamap + ((writeMedia verbose dir (joinPath fp, contents)):)) [] mediamap writeMedia :: Bool -> FilePath -> (FilePath, BL.ByteString) -> IO () writeMedia verbose dir (subpath, bs) = do -- cgit v1.2.3 From cc07d0c6bfac7081118d3cbf0baea197593adc11 Mon Sep 17 00:00:00 2001 From: mpickering Date: Thu, 25 Sep 2014 12:42:53 +0100 Subject: Shared: Make collapseFilePath OS-agnostic --- src/Text/Pandoc/Shared.hs | 14 +++++++++----- tests/Tests/Shared.hs | 37 +++++++++++++++++++------------------ 2 files changed, 28 insertions(+), 23 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 2d7c08718..6e1f84335 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -1,5 +1,6 @@ {-# LANGUAGE DeriveDataTypeable, CPP, MultiParamTypeClasses, - FlexibleContexts, ScopedTypeVariables, PatternGuards #-} + FlexibleContexts, ScopedTypeVariables, PatternGuards, + ViewPatterns #-} {- Copyright (C) 2006-2014 John MacFarlane @@ -106,7 +107,7 @@ import Network.URI ( escapeURIString, isURI, nonStrictRelativeTo, unEscapeString, parseURIReference, isAllowedInURI ) import qualified Data.Set as Set import System.Directory -import System.FilePath (joinPath, splitDirectories) +import System.FilePath (joinPath, splitDirectories, pathSeparator, isPathSeparator) import Text.Pandoc.MIME (MimeType, getMimeType) import System.FilePath ( (), takeExtension, dropExtension) import Data.Generics (Typeable, Data) @@ -871,11 +872,14 @@ collapseFilePath = joinPath . reverse . foldl go [] . splitDirectories go rs "." = rs go r@(p:rs) ".." = case p of ".." -> ("..":r) - "/" -> ("..":r) + (checkPathSeperator -> Just True) -> ("..":r) _ -> rs - go _ "/" = ["/"] + go _ (checkPathSeperator -> Just True) = [[pathSeparator]] go rs x = x:rs - + isSingleton [] = Nothing + isSingleton [x] = Just x + isSingleton _ = Nothing + checkPathSeperator = fmap isPathSeparator . isSingleton -- -- Safe read diff --git a/tests/Tests/Shared.hs b/tests/Tests/Shared.hs index b6671835c..9b55b7b1d 100644 --- a/tests/Tests/Shared.hs +++ b/tests/Tests/Shared.hs @@ -9,6 +9,7 @@ import Test.Framework.Providers.HUnit import Test.HUnit ( assertBool, (@?=) ) import Text.Pandoc.Builder import Data.Monoid +import System.FilePath (joinPath) tests :: [Test] tests = [ testGroup "normalize" @@ -40,21 +41,21 @@ p_normalize_no_trailing_spaces ils = null ils' || last ils' /= Space testCollapse :: [Test] testCollapse = map (testCase "collapse") - [ (collapseFilePath "" @?= "") - , (collapseFilePath "./foo" @?= "foo") - , (collapseFilePath "././../foo" @?= "../foo") - , (collapseFilePath "../foo" @?= "../foo") - , (collapseFilePath "/bar/../baz" @?= "/baz") - , (collapseFilePath "/../baz" @?= "/../baz") - , (collapseFilePath "./foo/.././bar/../././baz" @?= "baz") - , (collapseFilePath "./" @?= "") - , (collapseFilePath "././" @?= "") - , (collapseFilePath "../" @?= "..") - , (collapseFilePath ".././" @?= "..") - , (collapseFilePath "./../" @?= "..") - , (collapseFilePath "../../" @?= "../..") - , (collapseFilePath "parent/foo/baz/../bar" @?= "parent/foo/bar") - , (collapseFilePath "parent/foo/baz/../../bar" @?= "parent/bar") - , (collapseFilePath "parent/foo/.." @?= "parent") - , (collapseFilePath "/parent/foo/../../bar" @?= "/bar") - , (collapseFilePath "/./parent/foo" @?= "/parent/foo")] + [ (collapseFilePath (joinPath [ ""]) @?= (joinPath [ ""])) + , (collapseFilePath (joinPath [ ".","foo"]) @?= (joinPath [ "foo"])) + , (collapseFilePath (joinPath [ ".",".","..","foo"]) @?= (joinPath [ joinPath ["..", "foo"]])) + , (collapseFilePath (joinPath [ "..","foo"]) @?= (joinPath [ "..","foo"])) + , (collapseFilePath (joinPath [ "","bar","..","baz"]) @?= (joinPath [ "","baz"])) + , (collapseFilePath (joinPath [ "","..","baz"]) @?= (joinPath [ "","..","baz"])) + , (collapseFilePath (joinPath [ ".","foo","..",".","bar","..",".",".","baz"]) @?= (joinPath [ "baz"])) + , (collapseFilePath (joinPath [ ".",""]) @?= (joinPath [ ""])) + , (collapseFilePath (joinPath [ ".",".",""]) @?= (joinPath [ ""])) + , (collapseFilePath (joinPath [ "..",""]) @?= (joinPath [ ".."])) + , (collapseFilePath (joinPath [ "..",".",""]) @?= (joinPath [ ".."])) + , (collapseFilePath (joinPath [ ".","..",""]) @?= (joinPath [ ".."])) + , (collapseFilePath (joinPath [ "..","..",""]) @?= (joinPath [ "..",".."])) + , (collapseFilePath (joinPath [ "parent","foo","baz","..","bar"]) @?= (joinPath [ "parent","foo","bar"])) + , (collapseFilePath (joinPath [ "parent","foo","baz","..","..","bar"]) @?= (joinPath [ "parent","bar"])) + , (collapseFilePath (joinPath [ "parent","foo",".."]) @?= (joinPath [ "parent"])) + , (collapseFilePath (joinPath [ "","parent","foo","..","..","bar"]) @?= (joinPath [ "","bar"])) + , (collapseFilePath (joinPath [ "",".","parent","foo"]) @?= (joinPath [ "","parent","foo"]))] -- cgit v1.2.3 From 575c76e36bba6ab6dab5b6e68cffb66a1842d460 Mon Sep 17 00:00:00 2001 From: mpickering Date: Thu, 25 Sep 2014 15:28:50 +0100 Subject: HTML Writer: MathML now outputted with tex annotation. Closes #1635 --- src/Text/Pandoc/Writers/HTML.hs | 16 +++++++++++++++- 1 file changed, 15 insertions(+), 1 deletion(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 9ead604d7..8106806cf 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -60,6 +60,8 @@ import qualified Text.Blaze.XHtml1.Transitional.Attributes as A import Text.Blaze.Renderer.String (renderHtml) import Text.TeXMath import Text.XML.Light.Output +import Text.XML.Light (unode, elChildren, add_attr, unqual) +import qualified Text.XML.Light as XML import System.FilePath (takeExtension) import Data.Monoid import Data.Aeson (Value) @@ -615,6 +617,18 @@ inlineListToHtml :: WriterOptions -> [Inline] -> State WriterState Html inlineListToHtml opts lst = mapM (inlineToHtml opts) lst >>= return . mconcat +-- | Annotates a MathML expression with the tex source +annotateMML :: XML.Element -> String -> XML.Element +annotateMML e tex = math (unode "semantics" [cs, unode "annotation" (annotAttrs, tex)]) + where + cs = case elChildren e of + [] -> unode "mrow" () + [x] -> x + xs -> unode "mrow" xs + math = add_attr (XML.Attr (unqual "xmlns") "http://www.w3.org/1998/Math/MathML") . unode "math" + annotAttrs = [XML.Attr (unqual "encoding") "application/x-tex"] + + -- | Convert Pandoc inline element to HTML. inlineToHtml :: WriterOptions -> Inline -> State WriterState Html inlineToHtml opts inline = @@ -706,7 +720,7 @@ inlineToHtml opts inline = defaultConfigPP case writeMathML dt <$> readTeX str of Right r -> return $ preEscapedString $ - ppcElement conf r + ppcElement conf (annotateMML r str) Left _ -> inlineListToHtml opts (texMathToInlines t str) >>= return . (H.span ! A.class_ "math") -- cgit v1.2.3 From 515a120d0425318d6c8b95c4d8f8d0b1a48193d2 Mon Sep 17 00:00:00 2001 From: mpickering Date: Thu, 25 Sep 2014 18:23:28 +0100 Subject: Add support for KaTeX HTML math Closes #1626 --- pandoc.hs | 35 ++++++++++++++++++++++++++++++++--- src/Text/Pandoc/Options.hs | 1 + src/Text/Pandoc/Writers/HTML.hs | 19 +++++++++++++++++++ 3 files changed, 52 insertions(+), 3 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/pandoc.hs b/pandoc.hs index a9bea12c6..71d0c4b98 100644 --- a/pandoc.hs +++ b/pandoc.hs @@ -58,7 +58,7 @@ import qualified Control.Exception as E import Control.Exception.Extensible ( throwIO ) import qualified Text.Pandoc.UTF8 as UTF8 import Control.Monad (when, unless, (>=>)) -import Data.Maybe (isJust) +import Data.Maybe (isJust, fromMaybe) import Data.Foldable (foldrM) import Network.URI (parseURI, isURI, URI(..)) import qualified Data.ByteString.Lazy as B @@ -68,7 +68,7 @@ import qualified Data.Map as M import Data.Yaml (decode) import qualified Data.Yaml as Yaml import qualified Data.Text as T -import Control.Applicative ((<$>)) +import Control.Applicative ((<$>), (<|>)) import Text.Pandoc.Readers.Txt2Tags (getT2TMeta) import Data.Monoid @@ -205,6 +205,8 @@ data Opt = Opt , optExtractMedia :: Maybe FilePath -- ^ Path to extract embedded media , optTrace :: Bool -- ^ Print debug information , optTrackChanges :: TrackChanges -- ^ Accept or reject MS Word track-changes. + , optKaTeXStylesheet :: Maybe String -- ^ Path to stylesheet for KaTeX + , optKaTeXJS :: Maybe String -- ^ Path to js file for KaTeX } -- | Defaults for command-line options. @@ -263,6 +265,8 @@ defaultOpts = Opt , optExtractMedia = Nothing , optTrace = False , optTrackChanges = AcceptChanges + , optKaTeXStylesheet = Nothing + , optKaTeXJS = Nothing } -- | A list of functions, each transforming the options data structure @@ -818,6 +822,21 @@ options = return opt { optHTMLMathMethod = MathJax url'}) "URL") "" -- "Use MathJax for HTML math" + , Option "" ["katex"] + (OptArg + (\arg opt -> + return opt + { optKaTeXJS = + arg <|> Just "http://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.1.0/katex.min.js"}) + "URL") + "" -- Use KaTeX for HTML Math + + , Option "" ["katex-stylesheet"] + (ReqArg + (\arg opt -> + return opt { optKaTeXStylesheet = Just arg }) + "URL") + "" -- Set the KaTeX Stylesheet location , Option "" ["gladtex"] (NoArg @@ -860,6 +879,7 @@ options = ] + addMetadata :: String -> MetaValue -> M.Map String MetaValue -> M.Map String MetaValue addMetadata k v m = case M.lookup k m of @@ -1027,7 +1047,7 @@ main = do , optHighlight = highlight , optHighlightStyle = highlightStyle , optChapters = chapters - , optHTMLMathMethod = mathMethod + , optHTMLMathMethod = mathMethod' , optReferenceODT = referenceODT , optReferenceDocx = referenceDocx , optEpubStylesheet = epubStylesheet @@ -1056,6 +1076,8 @@ main = do , optExtractMedia = mbExtractMedia , optTrace = trace , optTrackChanges = trackChanges + , optKaTeXStylesheet = katexStylesheet + , optKaTeXJS = katexJS } = opts when dumpArgs $ @@ -1063,6 +1085,13 @@ main = do mapM_ (\arg -> UTF8.hPutStrLn stdout arg) args exitWith ExitSuccess + let csscdn = "http://cdnjs.cloudflare.com/ajax/libs/KaTeX/0.1.0/katex.min.css" + let mathMethod = + case (katexJS, katexStylesheet) of + (Nothing, _) -> mathMethod' + (Just js, ss) -> KaTeX js (fromMaybe csscdn ss) + + -- --bibliography implies -F pandoc-citeproc for backwards compatibility: let needsCiteproc = isJust (M.lookup "bibliography" metadata) && optCiteMethod opts `notElem` [Natbib, Biblatex] && diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 84ccbbdc9..ebfd8f8a9 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -251,6 +251,7 @@ data HTMLMathMethod = PlainMath | WebTeX String -- url of TeX->image script. | MathML (Maybe String) -- url of MathMLinHTML.js | MathJax String -- url of MathJax.js + | KaTeX String String -- url of stylesheet and katex.js deriving (Show, Read, Eq) data CiteMethod = Citeproc -- use citeproc to render them diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 8106806cf..652fc979f 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -157,6 +157,10 @@ pandocToHtml opts (Pandoc meta blocks) = do H.script ! A.src (toValue url) ! A.type_ "text/javascript" $ mempty + KaTeX js css -> + (H.script ! A.src (toValue js) $ mempty) <> + (H.link ! A.rel "stylesheet" ! A.href (toValue css)) <> + (H.script ! A.type_ "text/javascript" $ toHtml renderKaTeX) _ -> case lookup "mathml-script" (writerVariables opts) of Just s | not (writerHtml5 opts) -> H.script ! A.type_ "text/javascript" @@ -728,6 +732,10 @@ inlineToHtml opts inline = case t of InlineMath -> "\\(" ++ str ++ "\\)" DisplayMath -> "\\[" ++ str ++ "\\]" + KaTeX _ _ -> return $ H.span ! A.class_ "math" $ + toHtml (case t of + InlineMath -> str + DisplayMath -> "\\displaystyle " ++ str) PlainMath -> do x <- inlineListToHtml opts (texMathToInlines t str) let m = H.span ! A.class_ "math" $ x @@ -829,3 +837,14 @@ blockListToNote opts ref blocks = Just EPUB3 -> noteItem ! customAttribute "epub:type" "footnote" _ -> noteItem return $ nl opts >> noteItem' + +-- Javascript snippet to render all KaTeX elements +renderKaTeX :: String +renderKaTeX = unlines [ + "window.onload = function(){var mathElements = document.getElementsByClassName(\"math\");" + , "for (var i=0; i < mathElements.length; i++)" + , "{" + , " var texText = mathElements[i].firstChild" + , " katex.render(texText.data, mathElements[i])" + , "}}" + ] -- cgit v1.2.3 From 1f0ba8ec11763d6f6335e0355402c5f4570850e8 Mon Sep 17 00:00:00 2001 From: mpickering Date: Thu, 25 Sep 2014 18:46:36 +0100 Subject: HTML Writer: Don't double render when email-obfuscation=none Closes #1625 --- src/Text/Pandoc/Writers/HTML.hs | 10 +++++----- 1 file changed, 5 insertions(+), 5 deletions(-) (limited to 'src/Text/Pandoc') diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 652fc979f..1a00c7660 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE OverloadedStrings, CPP #-} +{-# LANGUAGE OverloadedStrings, CPP, ViewPatterns #-} {-# OPTIONS_GHC -fno-warn-deprecations #-} {- Copyright (C) 2006-2014 John MacFarlane @@ -348,10 +348,10 @@ parseMailto s = do _ -> fail "not a mailto: URL" -- | Obfuscate a "mailto:" link. -obfuscateLink :: WriterOptions -> String -> String -> Html +obfuscateLink :: WriterOptions -> Html -> String -> Html obfuscateLink opts txt s | writerEmailObfuscation opts == NoObfuscation = - H.a ! A.href (toValue s) $ toHtml txt -obfuscateLink opts txt s = + H.a ! A.href (toValue s) $ txt +obfuscateLink opts (renderHtml -> txt) s = let meth = writerEmailObfuscation opts s' = map toLower (take 7 s) ++ drop 7 s in case parseMailto s' of @@ -753,7 +753,7 @@ inlineToHtml opts inline = | otherwise -> return mempty (Link txt (s,_)) | "mailto:" `isPrefixOf` s -> do linkText <- inlineListToHtml opts txt - return $ obfuscateLink opts (renderHtml linkText) s + return $ obfuscateLink opts linkText s (Link txt (s,tit)) -> do linkText <- inlineListToHtml opts txt let s' = case s of -- cgit v1.2.3 From 6740a9592a4cc20b501ea5c8d35c9fcb27203af0 Mon Sep 17 00:00:00 2001 From: mpickering Date: Thu, 25 Sep 2014 19:20:12 +0100 Subject: HTML Reader: Recognise
tags inside
 blocks

Closes #1620
---
 src/Text/Pandoc/Readers/HTML.hs | 7 ++++++-
 1 file changed, 6 insertions(+), 1 deletion(-)

(limited to 'src/Text/Pandoc')

diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index 4ea5f41d5..4e0bb375a 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -440,7 +440,7 @@ pCodeBlock :: TagParser Blocks
 pCodeBlock = try $ do
   TagOpen _ attr <- pSatisfy (~== TagOpen "pre" [])
   contents <- manyTill pAnyTag (pCloses "pre" <|> eof)
-  let rawText = concatMap fromTagText $ filter isTagText contents
+  let rawText = concatMap tagToString contents
   -- drop leading newline if any
   let result' = case rawText of
                      '\n':xs  -> xs
@@ -451,6 +451,11 @@ pCodeBlock = try $ do
                     _        -> result'
   return $ B.codeBlockWith (mkAttr attr) result
 
+tagToString :: Tag String -> String
+tagToString (TagText s) = s
+tagToString (TagOpen "br" _) = "\n"
+tagToString _ = ""
+
 inline :: TagParser Inlines
 inline = choice
            [ eNoteref
-- 
cgit v1.2.3


From 5cb475c37491db4bdffebfd06e55984ff118c10b Mon Sep 17 00:00:00 2001
From: Matthew Pickering 
Date: Sat, 27 Sep 2014 22:37:54 +0100
Subject: Org Reader: Parse multi-inline terms correctly in definition list

Closes #1649
---
 src/Text/Pandoc/Readers/Org.hs | 2 +-
 1 file changed, 1 insertion(+), 1 deletion(-)

(limited to 'src/Text/Pandoc')

diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs
index b07f96846..5c00a1b27 100644
--- a/src/Text/Pandoc/Readers/Org.hs
+++ b/src/Text/Pandoc/Readers/Org.hs
@@ -863,7 +863,7 @@ definitionListItem parseMarkerGetLength = try $ do
   line1 <- anyLineNewline
   blank <- option "" ("\n" <$ blankline)
   cont <- concat <$> many (listContinuation markerLength)
-  term' <- parseFromString inline term
+  term' <- parseFromString parseInlines term
   contents' <- parseFromString parseBlocks $ line1 ++ blank ++ cont
   return $ (,) <$> term' <*> fmap (:[]) contents'
 
-- 
cgit v1.2.3