aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--README13
-rw-r--r--pandoc.hs35
-rw-r--r--src/Text/Pandoc/MediaBag.hs10
-rw-r--r--src/Text/Pandoc/Options.hs1
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs7
-rw-r--r--src/Text/Pandoc/Readers/Org.hs2
-rw-r--r--src/Text/Pandoc/Shared.hs14
-rw-r--r--src/Text/Pandoc/Writers/HTML.hs45
-rw-r--r--tests/Tests/Readers/EPUB.hs5
-rw-r--r--tests/Tests/Readers/Org.hs4
-rw-r--r--tests/Tests/Shared.hs37
-rw-r--r--tests/epub/features.epubbin67495 -> 66370 bytes
-rw-r--r--tests/epub/features.native38
-rw-r--r--tests/epub/img.epubbin0 -> 61768 bytes
14 files changed, 135 insertions, 76 deletions
diff --git a/README b/README
index 93fbde8ab..9baa9060a 100644
--- a/README
+++ b/README
@@ -710,6 +710,16 @@ Math rendering in HTML
formulas to images. The formula will be concatenated with the URL
provided. If *URL* is not specified, the Google Chart API will be used.
+`--katex`[=*URL*]
+: Use [KaTeX] to display embedded TeX math in HTML output.
+ The *URL* should point to the `katex.js` load script. If a *URL* is
+ not provided, a link to the KaTeX CDN will be inserted.
+
+`--katex-stylesheet=*URL*`
+: The *URL* should point to the `katex.css` stylesheet. If this option is
+ not specified, a link to the KaTeX CDN will be inserted. Note that this
+ option does not imply `--katex`.
+
Options for wrapper scripts
---------------------------
@@ -1652,7 +1662,7 @@ proportionally spaced fonts, as it does not require lining up columns.
#### Extension: `table_captions` ####
-A caption may optionally be provided with all 4 kinds of tables (as
+A caption may optionally be provided with all 4 kinds of tables (as
illustrated in the examples below). A caption is a paragraph beginning
with the string `Table:` (or just `:`), which will be stripped off.
It may appear either before or after the table.
@@ -3177,3 +3187,4 @@ Rosenthal.
[txt2tags]: http://txt2tags.org/
[EPUB]: http://idpf.org/epub
[EPUBspine]: http://www.idpf.org/epub/301/spec/epub-publications.html#sec-spine-elem
+[KaTeX]: https://github.com/Khan/KaTeX
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/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
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/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
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'
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 <jgm@berkeley.edu>
@@ -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/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs
index 9ead604d7..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 <jgm@berkeley.edu>
@@ -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)
@@ -155,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"
@@ -342,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
@@ -615,6 +621,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 +724,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")
@@ -714,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
@@ -731,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
@@ -815,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])"
+ , "}}"
+ ]
diff --git a/tests/Tests/Readers/EPUB.hs b/tests/Tests/Readers/EPUB.hs
index f27ea979f..0d19a8400 100644
--- a/tests/Tests/Readers/EPUB.hs
+++ b/tests/Tests/Readers/EPUB.hs
@@ -8,6 +8,7 @@ import qualified Data.ByteString.Lazy as BL
import Text.Pandoc.Readers.EPUB
import Text.Pandoc.MediaBag (MediaBag, mediaDirectory)
import Control.Applicative
+import System.FilePath (joinPath)
getMediaBag :: FilePath -> IO MediaBag
getMediaBag fp = snd . readEPUB def <$> BL.readFile fp
@@ -22,12 +23,12 @@ testMediaBag fp bag = do
(actBag == bag)
featuresBag :: [(String, String, Int)]
-featuresBag = [("img/ElementaryMathExample.png","image/png",1331),("img/Maghreb1.png","image/png",2520),("img/check.gif","image/gif",1340),("img/check.jpg","image/jpeg",2661),("img/check.png","image/png",2815),("img/cichons_diagram.png","image/png",7045),("img/complex_number.png","image/png",5238),("img/multiscripts_and_greek_alphabet.png","image/png",10060)]
+featuresBag = [(joinPath ["img","check.gif"],"image/gif",1340),(joinPath ["img","check.jpg"],"image/jpeg",2661),(joinPath ["img","check.png"],"image/png",2815),(joinPath ["img","multiscripts_and_greek_alphabet.png"],"image/png",10060)]
tests :: [Test]
tests =
[ testGroup "EPUB Mediabag"
[ testCase "features bag"
- (testMediaBag "epub/features.epub" featuresBag)
+ (testMediaBag "epub/img.epub" featuresBag)
]
]
diff --git a/tests/Tests/Readers/Org.hs b/tests/Tests/Readers/Org.hs
index b9896e1b0..92ec8155b 100644
--- a/tests/Tests/Readers/Org.hs
+++ b/tests/Tests/Readers/Org.hs
@@ -702,7 +702,9 @@ tests =
]
])
]
-
+ , "Definition list with multi-word term" =:
+ " - Elijah Wood :: He plays Frodo" =?>
+ definitionList [ ("Elijah" <> space <> "Wood", [plain $ "He" <> space <> "plays" <> space <> "Frodo"])]
, "Compact definition list" =:
unlines [ "- ATP :: adenosine 5' triphosphate"
, "- DNA :: deoxyribonucleic acid"
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"]))]
diff --git a/tests/epub/features.epub b/tests/epub/features.epub
index 8dcae384b..2690eec8b 100644
--- a/tests/epub/features.epub
+++ b/tests/epub/features.epub
Binary files differ
diff --git a/tests/epub/features.native b/tests/epub/features.native
index f01070383..6ccc04f43 100644
--- a/tests/epub/features.native
+++ b/tests/epub/features.native
@@ -1,5 +1,4 @@
-[Para [Image [] ("img/multiscripts_and_greek_alphabet.png","")]
-,Para [Span ("front.xhtml",[],[]) []]
+[Para [Span ("front.xhtml",[],[]) []]
,RawBlock (Format "html") "<section>"
,Header 1 ("",[],[]) [Str "Reflowable",Space,Str "EPUB",Space,Str "3",Space,Str "Conformance",Space,Str "Test",Space,Str "Document:",Space,Str "0100"]
,RawBlock (Format "html") "<section>"
@@ -28,31 +27,6 @@
[[Plain [Str "@@@TODO",Space,Str "provide",Space,Str "info",Space,Str "on",Space,Str "where",Space,Str "to",Space,Str "get",Space,Str "the",Space,Str "results",Space,Str "form"]]])]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
-,Para [Span ("content-images-001.xhtml",[],[]) []]
-,RawBlock (Format "html") "<section>"
-,Header 2 ("content-images-001.xhtml#multimedia",[],[]) [Str "Multimedia"]
-,RawBlock (Format "html") "<section>"
-,Header 3 ("content-images-001.xhtml#images",[],[]) [Str "Images"]
-,RawBlock (Format "html") "<section id=\"img-010\" class=\"ctest\">"
-,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "img-010"],Space,Str "GIF"]
-,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Str "GIF",Space,Str "image",Space,Str "format",Space,Str "is",Space,Str "supported."]
-,Para [Image [Str "gif",Space,Str "test"] ("img/check.gif","")]
-,Para [Str "If",Space,Str "a",Space,Str "checkmark",Space,Str "precedes",Space,Str "this",Space,Str "paragaph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
-,RawBlock (Format "html") "</section>"
-,RawBlock (Format "html") "<section id=\"img-020\" class=\"ctest\">"
-,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "img-020"],Space,Str "PNG"]
-,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Str "PNG",Space,Str "image",Space,Str "format",Space,Str "is",Space,Str "supported."]
-,Para [Image [Str "png",Space,Str "test"] ("img/check.png","")]
-,Para [Str "If",Space,Str "a",Space,Str "checkmark",Space,Str "precedes",Space,Str "this",Space,Str "paragaph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
-,RawBlock (Format "html") "</section>"
-,RawBlock (Format "html") "<section id=\"img-030\" class=\"ctest\">"
-,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "img-030"],Space,Str "JPEG"]
-,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Str "JPEG",Space,Str "image",Space,Str "format",Space,Str "is",Space,Str "supported."]
-,Para [Image [Str "jpeg",Space,Str "test"] ("img/check.jpg","")]
-,Para [Str "If",Space,Str "a",Space,Str "checkmark",Space,Str "precedes",Space,Str "this",Space,Str "paragaph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
-,RawBlock (Format "html") "</section>"
-,RawBlock (Format "html") "</section>"
-,RawBlock (Format "html") "</section>"
,Para [Span ("content-mathml-001.xhtml",[],[]) []]
,RawBlock (Format "html") "<section>"
,Header 2 ("content-mathml-001.xhtml#mathml",[],[]) [Str "MathML"]
@@ -94,13 +68,13 @@
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "mathml-024"],Str "Horizontal",Space,Str "stretch,",Space,Code ("",[],[]) "mover",Str ",",Space,Code ("",[],[]) "munder",Str ",",Space,Str "and",Space,Code ("",[],[]) "mspace",Space,Str "elements"]
,Para [Str "Tests",Space,Str "whether",Space,Str "horizontal",Space,Str "stretch,",Space,Code ("",[],[]) "mover",Str ",",Space,Code ("",[],[]) "munder",Str ",",Space,Code ("",[],[]) "mspace",Space,Str "elements",Space,Str "are",Space,Str "supported."]
,Para [Math DisplayMath "c = \\overset{\\text{complex\\ number}}{\\overbrace{\\underset{\\text{real}}{\\underbrace{\\mspace{20mu} a\\mspace{20mu}}} + \\underset{\\text{imaginary}}{\\underbrace{\\quad b{\\mathbb{i}}\\quad}}}}"]
-,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Image [Str "description",Space,Str "of",Space,Str "imaginary",Space,Str "number:",Space,Str "c",Space,Str "=",Space,Str "a",Space,Str "+bi",Space,Str "with",Space,Str "an",Space,Str "overbrace",Space,Str "reading",Space,Str "'complex",Space,Str "number'",Space,Str "and",Space,Str "underbraces",Space,Str "below",Space,Str "'a'",Space,Str "and",Space,Str "'b",Space,Str "i'",Space,Str "reading",Space,Str "'real'",Space,Str "and",Space,Str "'imaginary'",Space,Str "respectively."] ("img/complex_number.png",""),Str "."]
+,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Str "."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"mathml-025\" class=\"ctest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "mathml-025"],Str "Testing",Space,Code ("",[],[]) "mtable",Space,Str "with",Space,Code ("",[],[]) "colspan",Space,Str "and",Space,Code ("",[],[]) "rowspan",Space,Str "attributes,",Space,Str "Hebrew",Space,Str "and",Space,Str "Script",Space,Str "fonts"]
,Para [Str "Tests",Space,Str "whether",Space,Code ("",[],[]) "mtable",Space,Str "with",Space,Code ("",[],[]) "colspan",Space,Str "and",Space,Code ("",[],[]) "mspace",Space,Str "attributes",Space,Str "(colum",Space,Str "and",Space,Str "row",Space,Str "spanning)",Space,Str "are",Space,Str "supported;",Space,Str "uses",Space,Str "Hebrew",Space,Str "and",Space,Str "Script",Space,Str "alphabets."]
,Para [Math DisplayMath "\\begin{array}{llllllllll}\n & {\\operatorname{cov}\\left( \\mathcal{L} \\right)} & \\longrightarrow & {\\operatorname{non}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cof}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cof}\\left( \\mathcal{L} \\right)} & \\longrightarrow & 2^{\\aleph_{0}} \\\\\n & \\uparrow & & \\uparrow & & \\uparrow & & \\uparrow & & \\\\\n & {\\mathfrak{b}} & \\longrightarrow & {\\mathfrak{d}} & & & & & & \\\\\n & \\uparrow & & \\uparrow & & & & & & \\\\\n\\aleph_{1} & \\longrightarrow & {\\operatorname{add}\\left( \\mathcal{L} \\right)} & \\longrightarrow & {\\operatorname{add}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cov}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{non}\\left( \\mathcal{L} \\right)} & \\\\\n\\end{array}"]
-,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Link [Str "Cicho\324's",Space,Str "Diagram"] ("Cicho%C5%84's_diagram",""),Str ":",Space,Image [Str "rendering",Space,Str "of",Space,Str "Cicho\324's",Space,Str "diagram."] ("img/cichons_diagram.png",""),Str "."]
+,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Link [Str "Cicho\324's",Space,Str "Diagram"] ("Cicho%C5%84's_diagram",""),Str ":",Space,Str "."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"mathml-026\" class=\"ctest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "mathml-026"],Str "BiDi,",Space,Str "RTL",Space,Str "and",Space,Str "Arabic",Space,Str "alphabets"]
@@ -111,7 +85,7 @@
,RawBlock (Format "html") "<section id=\"mathml-027\" class=\"ctest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "mathml-027"],Str "Elementary",Space,Str "math:",Space,Str "long",Space,Str "division",Space,Str "notation"]
,Para [Str "Tests",Space,Str "whether",Space,Code ("",[],[]) "mlongdiv",Space,Str "elements",Space,Str "(from",Space,Str "elementary",Space,Str "math)",Space,Str "are",Space,Str "supported."]
-,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Str "the",Space,Str "following",Space,Str "image:",Space,Image [Str "A",Space,Str "long",Space,Str "division",Space,Str "dividing",Space,Str "1306",Space,Str "by",Space,Str "3,",Space,Str "presented",Space,Str "in",Space,Str "'lefttop'",Space,Str "(US)",Space,Str "notation"] ("img/ElementaryMathExample.png",""),Str "."]
+,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Str "the",Space,Str "following",Space,Str "image:",Space,Str "."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,Para [Span ("content-switch-001.xhtml",[],[]) []]
@@ -130,6 +104,4 @@
,Para [Str "If",Space,Str "a",Space,Str "MathML",Space,Str "equation",Space,Str "is",Space,Str "rendered",Space,Str "before",Space,Str "this",Space,Str "paragraph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,Para [Str "If",Space,Str "test",Space,Code ("",[],[]) "switch-010",Space,Str "did",Space,Str "not",Space,Str "pass,",Space,Str "this",Space,Str "test",Space,Str "should",Space,Str "be",Space,Str "marked",Space,Code ("",[],[]) "Not Supported",Str "."]
,RawBlock (Format "html") "</section>"
-,RawBlock (Format "html") "</section>"
-,Para [Span ("Maghreb1.png",[],[]) []]
-,Para [Image [] ("img/Maghreb1.png","")]]
+,RawBlock (Format "html") "</section>"]
diff --git a/tests/epub/img.epub b/tests/epub/img.epub
new file mode 100644
index 000000000..ebe80d935
--- /dev/null
+++ b/tests/epub/img.epub
Binary files differ