Merge branch 'epubend' of https://github.com/mpickering/pandoc into mpickering-epubend

Conflicts:
	pandoc.cabal
This commit is contained in:
John MacFarlane 2014-08-04 07:36:18 -07:00
commit 4630cff2a6
13 changed files with 1462 additions and 44 deletions

13
README
View file

@ -14,7 +14,7 @@ Pandoc is a [Haskell] library for converting from one markup format to
another, and a command-line tool that uses this library. It can read
[markdown] and (subsets of) [Textile], [reStructuredText], [HTML],
[LaTeX], [MediaWiki markup], [Haddock markup], [OPML], [Emacs
Org-mode], [DocBook], [txt2tags] and [Word docx]; and it can write plain text,
Org-mode], [DocBook], [txt2tags], [EPUB] and [Word docx]; and it can write plain text,
[markdown], [reStructuredText], [XHTML], [HTML 5], [LaTeX] (including
[beamer] slide shows), [ConTeXt], [RTF], [OPML], [DocBook],
[OpenDocument], [ODT], [Word docx], [GNU Texinfo], [MediaWiki markup],
@ -56,7 +56,8 @@ pandoc will fetch the content using HTTP:
pandoc -f html -t markdown http://www.fsf.org
If multiple input files are given, `pandoc` will concatenate them all (with
blank lines between them) before parsing.
blank lines between them) before parsing. This feature is disabled for
binary input formats such as `EPUB` and `docx`.
The format of the input and output can be specified explicitly using
command-line options. The input format can be specified using the
@ -144,9 +145,10 @@ General options
`markdown_phpextra` (PHP Markdown Extra extended markdown),
`markdown_github` (github extended markdown),
`textile` (Textile), `rst` (reStructuredText), `html` (HTML),
`docbook` (DocBook), `t2t` (txt2tags), `opml` (OPML), `org` (Emacs
Org-mode), `mediawiki` (MediaWiki markup), `haddock` (Haddock markup),
or `latex` (LaTeX). If `+lhs` is appended to `markdown`, `rst`,
`docbook` (DocBook), `t2t` (txt2tags), `docx` (docx), `epub` (EPUB),
`opml` (OPML), `org` (Emacs Org-mode), `mediawiki` (MediaWiki markup),
`haddock` (Haddock markup), or `latex` (LaTeX). If `+lhs` is appended
to `markdown`, `rst`,
`latex`, or `html`, the input will be treated as literate Haskell
source: see [Literate Haskell support](#literate-haskell-support),
below. Markdown syntax extensions can be individually enabled or
@ -3110,3 +3112,4 @@ Rosenthal.
[RFC5646]: http://tools.ietf.org/html/rfc5646
[InDesign ICML]: https://www.adobe.com/content/dam/Adobe/en/devnet/indesign/cs55-docs/IDML/idml-specification.pdf
[txt2tags]: http://txt2tags.org/
[EPUB]: http://idpf.org/epub

View file

@ -227,11 +227,11 @@ Library
old-locale >= 1 && < 1.1,
time >= 1.2 && < 1.5,
HTTP >= 4000.0.5 && < 4000.3,
texmath >= 0.6.6.3 && < 0.7,
texmath >= 0.7 && < 0.8,
xml >= 1.3.12 && < 1.4,
random >= 1 && < 1.1,
extensible-exceptions >= 0.1 && < 0.2,
pandoc-types >= 1.12.3.3 && < 1.13,
pandoc-types >= 1.12.4 && < 1.13,
aeson >= 0.7 && < 0.9,
tagsoup >= 0.13.1 && < 0.14,
base64-bytestring >= 0.1 && < 1.1,
@ -248,7 +248,8 @@ Library
binary >= 0.5 && < 0.8,
SHA >= 1.6 && < 1.7,
haddock-library >= 1.1 && < 1.2,
old-time
old-time,
deepseq-generics >= 0.1 && < 0.2
if flag(https)
Build-Depends: http-client >= 0.3.2 && < 0.4,
http-client-tls >= 0.2 && < 0.3,
@ -287,6 +288,7 @@ Library
Text.Pandoc.Readers.Native,
Text.Pandoc.Readers.Haddock,
Text.Pandoc.Readers.Docx,
Text.Pandoc.Readers.EPUB,
Text.Pandoc.Writers.Native,
Text.Pandoc.Writers.Docbook,
Text.Pandoc.Writers.OPML,
@ -340,7 +342,7 @@ Library
Executable pandoc
Build-Depends: pandoc,
pandoc-types >= 1.12.3.3 && < 1.13,
pandoc-types >= 1.12.4 && < 1.13,
base >= 4.2 && <5,
directory >= 1 && < 1.3,
filepath >= 1.1 && < 1.4,
@ -385,7 +387,7 @@ Test-Suite test-pandoc
Build-Depends: base >= 4.2 && < 5,
syb >= 0.1 && < 0.5,
pandoc,
pandoc-types >= 1.12.3.3 && < 1.13,
pandoc-types >= 1.12.4 && < 1.13,
bytestring >= 0.9 && < 0.11,
text >= 0.11 && < 1.2,
directory >= 1 && < 1.3,

View file

@ -896,6 +896,7 @@ defaultReaderName fallback (x:xs) =
".json" -> "json"
".docx" -> "docx"
".t2t" -> "t2t"
".epub" -> "epub"
_ -> defaultReaderName fallback xs
-- Returns True if extension of first source is .lhs

View file

@ -79,6 +79,7 @@ module Text.Pandoc
, readJSON
, readTxt2Tags
, readTxt2TagsNoMacros
, readEPUB
-- * Writers: converting /from/ Pandoc format
, Writer (..)
, writeNative
@ -134,6 +135,7 @@ import Text.Pandoc.Readers.Native
import Text.Pandoc.Readers.Haddock
import Text.Pandoc.Readers.Docx
import Text.Pandoc.Readers.Txt2Tags
import Text.Pandoc.Readers.EPUB
import Text.Pandoc.Writers.Native
import Text.Pandoc.Writers.Markdown
import Text.Pandoc.Writers.RST
@ -233,6 +235,7 @@ readers = [ ("native" , StringReader $ \_ s -> return $ readNative s)
,("haddock" , mkStringReader readHaddock)
,("docx" , mkBSReader readDocx)
,("t2t" , mkStringReader readTxt2TagsNoMacros)
,("epub" , mkBSReader readEPUB)
]
data Writer = PureStringWriter (WriterOptions -> Pandoc -> String)

View file

@ -1,7 +1,10 @@
{-# LANGUAGE CPP #-}
module Text.Pandoc.Compat.Except ( ExceptT
, Except
, Error(..)
, runExceptT
, runExcept
, MonadError
, throwError
, catchError )
where
@ -18,10 +21,17 @@ class Error a where
#else
import Control.Monad.Error
import Control.Monad.Identity (Identity, runIdentity)
type ExceptT = ErrorT
runExceptT :: ExceptT e m a -> m (Either e a)
type Except s a = ErrorT s Identity a
runExceptT :: ExceptT e m a -> m (Either e a)
runExceptT = runErrorT
runExcept :: ExceptT e Identity a -> Either e a
runExcept = runIdentity . runExceptT
#endif

View file

@ -106,6 +106,7 @@ data Extension =
| Ext_mmd_header_identifiers -- ^ Multimarkdown style header identifiers [myid]
| Ext_implicit_header_references -- ^ Implicit reference links for headers
| Ext_line_blocks -- ^ RST style line blocks
| Ext_epub_html_exts -- ^ Recognise the EPUB extended version of HTML
deriving (Show, Read, Enum, Eq, Ord, Bounded)
pandocExtensions :: Set Extension

View file

@ -0,0 +1,273 @@
{-# LANGUAGE
ViewPatterns
, StandaloneDeriving
, TupleSections
, FlexibleContexts #-}
module Text.Pandoc.Readers.EPUB
(readEPUB)
where
import Text.XML.Light
import Text.Pandoc.Definition hiding (Attr)
import Text.Pandoc.Walk (walk, query)
import Text.Pandoc.Generic(bottomUp)
import Text.Pandoc.Readers.HTML (readHtml)
import Text.Pandoc.Options ( ReaderOptions(..), readerExtensions, Extension(..)
, readerTrace)
import Text.Pandoc.Shared (escapeURI)
import Text.Pandoc.MediaBag (MediaBag, insertMedia)
import Text.Pandoc.Compat.Except (MonadError, throwError, runExcept, Except)
import qualified Text.Pandoc.Builder as B
import Codec.Archive.Zip ( Archive (..), toArchive, fromEntry
, findEntryByPath, Entry)
import qualified Data.ByteString.Lazy as BL (ByteString)
import System.FilePath (takeFileName, (</>), dropFileName, normalise)
import qualified Text.Pandoc.UTF8 as UTF8 (toStringLazy)
import Control.Applicative ((<$>))
import Control.Monad (guard, liftM, when)
import Data.Monoid (mempty, (<>))
import Data.List (isPrefixOf, isInfixOf)
import Data.Maybe (mapMaybe, fromMaybe)
import qualified Data.Map as M (Map, lookup, fromList, elems)
import qualified Data.Set as S (insert)
import Control.DeepSeq.Generics (deepseq, NFData)
import Debug.Trace (trace)
type MIME = String
type Items = M.Map String (FilePath, MIME)
readEPUB :: ReaderOptions -> BL.ByteString -> (Pandoc, MediaBag)
readEPUB opts bytes = runEPUB (archiveToEPUB opts $ toArchive bytes)
runEPUB :: Except String a -> a
runEPUB = either error id . runExcept
-- Note that internal reference are aggresively normalised so that all ids
-- are of the form "filename#id"
--
-- For now all paths are stripped from images
archiveToEPUB :: (MonadError String m) => ReaderOptions -> Archive -> m (Pandoc, MediaBag)
archiveToEPUB os archive = do
(root, content) <- getManifest archive
meta <- parseMeta content
(cover, items) <- parseManifest content
let coverDoc = fromMaybe mempty (imageToPandoc . takeFileName <$> cover)
spine <- parseSpine items content
let escapedSpine = map (escapeURI . takeFileName . fst) spine
Pandoc _ bs <-
foldM' (\a b -> ((a <>) . bottomUp (prependHash escapedSpine))
`liftM` parseSpineElem root b) mempty spine
let ast = coverDoc <> (Pandoc meta bs)
let mediaBag = fetchImages (M.elems items) root archive ast
return $ (ast, mediaBag)
where
rs = readerExtensions os
os' = os {readerExtensions = foldr S.insert rs [Ext_epub_html_exts, Ext_raw_html]}
os'' = os' {readerParseRaw = True}
parseSpineElem :: MonadError String m => FilePath -> (FilePath, MIME) -> m Pandoc
parseSpineElem r (path, mime) = do
when (readerTrace os) (traceM path)
doc <- mimeToReader mime (normalise (r </> path))
let docSpan = B.doc $ B.para $ B.spanWith (takeFileName path, [], []) mempty
return $ docSpan <> fixInternalReferences (takeFileName path) doc
mimeToReader :: MonadError String m => MIME -> FilePath -> m Pandoc
mimeToReader "application/xhtml+xml" path = do
fname <- findEntryByPathE path archive
return $ readHtml os'' . UTF8.toStringLazy $ fromEntry fname
mimeToReader s path
| s `elem` imageMimes = return $ imageToPandoc path
| otherwise = return $ mempty
fetchImages :: [(FilePath, MIME)]
-> FilePath
-> Archive
-> Pandoc
-> MediaBag
fetchImages mimes root a (query iq -> links) =
foldr (uncurry3 insertMedia) mempty
(mapMaybe getEntry links)
where
getEntry l = let mediaPos = normalise (root </> l) in
(l , lookup mediaPos mimes, ) . fromEntry
<$> findEntryByPath mediaPos a
iq :: Inline -> [FilePath]
iq (Image _ (url, _)) = [url]
iq _ = []
imageToPandoc :: FilePath -> Pandoc
imageToPandoc s = B.doc . B.para $ B.image s "" mempty
imageMimes :: [String]
imageMimes = ["image/gif", "image/jpeg", "image/png"]
type CoverImage = FilePath
parseManifest :: (MonadError String m) => Element -> m (Maybe CoverImage, Items)
parseManifest content = do
manifest <- findElementE (dfName "manifest") content
let items = findChildren (dfName "item") manifest
r <- mapM parseItem items
let cover = findAttr (emptyName "href") =<< filterChild findCover manifest
return (cover, (M.fromList r))
where
findCover e = maybe False (isInfixOf "cover-image")
(findAttr (emptyName "properties") e)
parseItem e = do
uid <- findAttrE (emptyName "id") e
href <- findAttrE (emptyName "href") e
mime <- findAttrE (emptyName "media-type") e
return (uid, (href, mime))
parseSpine :: MonadError String m => Items -> Element -> m [(FilePath, MIME)]
parseSpine is e = do
spine <- findElementE (dfName "spine") e
let itemRefs = findChildren (dfName "itemref") spine
mapM (mkE "parseSpine" . (flip M.lookup is)) $ mapMaybe parseItemRef itemRefs
where
parseItemRef ref = do
let linear = maybe True (== "yes") (findAttr (emptyName "linear") ref)
guard linear
findAttr (emptyName "idref") ref
parseMeta :: MonadError String m => Element -> m Meta
parseMeta content = do
meta <- findElementE (dfName "metadata") content
let dcspace (QName _ (Just "http://purl.org/dc/elements/1.1/") (Just "dc")) = True
dcspace _ = False
let dcs = filterChildrenName dcspace meta
let r = foldr parseMetaItem nullMeta dcs
return r
-- http://www.idpf.org/epub/30/spec/epub30-publications.html#sec-metadata-elem
parseMetaItem :: Element -> Meta -> Meta
parseMetaItem e@(stripNamespace . elName -> field) meta =
B.setMeta (renameMeta field) (B.str $ strContent e) meta
renameMeta :: String -> String
renameMeta "creator" = "author"
renameMeta s = s
getManifest :: MonadError String m => Archive -> m (String, Element)
getManifest archive = do
metaEntry <- findEntryByPathE ("META-INF" </> "container.xml") archive
docElem <- (parseXMLDocE . UTF8.toStringLazy . fromEntry) metaEntry
let namespaces = mapMaybe attrToNSPair (elAttribs docElem)
ns <- mkE "xmlns not in namespaces" (lookup "xmlns" namespaces)
as <- liftM ((map attrToPair) . elAttribs)
(findElementE (QName "rootfile" (Just ns) Nothing) docElem)
root <- mkE "Root not found" (lookup "full-path" as)
let rootdir = dropFileName root
--mime <- lookup "media-type" as
manifest <- findEntryByPathE root archive
liftM ((,) rootdir) (parseXMLDocE . UTF8.toStringLazy . fromEntry $ manifest)
-- Fixup
fixInternalReferences :: String -> Pandoc -> Pandoc
fixInternalReferences s =
(walk normalisePath) . (walk $ fixBlockIRs s') . (walk $ fixInlineIRs s')
where
s' = escapeURI s
fixInlineIRs :: String -> Inline -> Inline
fixInlineIRs s (Span as v) =
Span (fixAttrs s as) v
fixInlineIRs s (Code as code) =
Code (fixAttrs s as) code
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] =
Link is ('#':url, tit)
| otherwise = l
prependHash _ i = i
fixBlockIRs :: String -> Block -> Block
fixBlockIRs s (Div as b) =
Div (fixAttrs s as) b
fixBlockIRs s (Header i as b) =
Header i (fixAttrs s as) b
fixBlockIRs s (CodeBlock as code) =
CodeBlock (fixAttrs s as) code
fixBlockIRs _ b = b
fixAttrs :: FilePath -> B.Attr -> B.Attr
fixAttrs s (ident, cs, kvs) = (addHash s ident, filter (not . null) cs, removeEPUBAttrs kvs)
addHash :: String -> String -> String
addHash _ "" = ""
addHash s ident = s ++ "#" ++ ident
removeEPUBAttrs :: [(String, String)] -> [(String, String)]
removeEPUBAttrs kvs = filter (not . isEPUBAttr) kvs
isEPUBAttr :: (String, String) -> Bool
isEPUBAttr (k, _) = "epub:" `isPrefixOf` k
-- Library
-- Strict version of foldM
foldM' :: (Monad m, NFData a) => (a -> b -> m a) -> a -> [b] -> m a
foldM' _ z [] = return z
foldM' f z (x:xs) = do
z' <- f z x
z' `deepseq` foldM' f z' xs
traceM :: Monad m => String -> m ()
traceM = flip trace (return ())
uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 f (a, b, c) = f a b c
-- Utility
stripNamespace :: QName -> String
stripNamespace (QName v _ _) = v
attrToNSPair :: Attr -> Maybe (String, String)
attrToNSPair (Attr (QName "xmlns" _ _) val) = Just ("xmlns", val)
attrToNSPair _ = Nothing
attrToPair :: Attr -> (String, String)
attrToPair (Attr (QName name _ _) val) = (name, val)
defaultNameSpace :: Maybe String
defaultNameSpace = Just "http://www.idpf.org/2007/opf"
dfName :: String -> QName
dfName s = QName s defaultNameSpace Nothing
emptyName :: String -> QName
emptyName s = QName s Nothing Nothing
-- Convert Maybe interface to Either
findAttrE :: MonadError String m => QName -> Element -> m String
findAttrE q e = mkE "findAttr" $ findAttr q e
findEntryByPathE :: MonadError String m => FilePath -> Archive -> m Entry
findEntryByPathE path a = mkE ("No entry on path: " ++ path) $ findEntryByPath path a
parseXMLDocE :: MonadError String m => String -> m Element
parseXMLDocE doc = mkE "Unable to parse XML doc" $ parseXMLDoc doc
findElementE :: MonadError String m => QName -> Element -> m Element
findElementE e x = mkE ("Unable to find element: " ++ show e) $ findElement e x
mkE :: MonadError String m => String -> Maybe a -> m a
mkE s = maybe (throwError s) return

View file

@ -41,48 +41,64 @@ import Text.HTML.TagSoup
import Text.HTML.TagSoup.Match
import Text.Pandoc.Definition
import qualified Text.Pandoc.Builder as B
import Text.Pandoc.Builder (HasMeta (..), Blocks, Inlines, trimInlines)
import Text.Pandoc.Shared
import Text.Pandoc.Options
import Text.Pandoc.Parsing
import Data.Maybe ( fromMaybe, isJust )
import Data.List ( intercalate )
import Text.Pandoc.Builder (Blocks, Inlines, trimInlines, HasMeta(..))
import Text.Pandoc.Shared ( extractSpaces, renderTags'
, escapeURI, safeRead )
import Text.Pandoc.Options (ReaderOptions(readerParseRaw, readerTrace)
, Extension (Ext_epub_html_exts))
import Text.Pandoc.Parsing hiding ((<|>))
import Text.Pandoc.Walk
import Data.Maybe ( fromMaybe, isJust)
import Data.List ( intercalate, isInfixOf )
import Data.Char ( isDigit )
import Control.Monad ( liftM, guard, when, mzero )
import Control.Applicative ( (<$>), (<$), (<*) )
import Data.Monoid
import Control.Monad ( liftM, guard, when, mzero, void, unless )
import Control.Arrow ((***))
import Control.Applicative ( (<$>), (<$), (<*), (*>), (<|>))
import Data.Monoid (mconcat, Monoid, mempty, (<>), First (..))
import Text.Printf (printf)
import Debug.Trace (trace)
import Data.Default (Default (..))
import Control.Monad.Reader (Reader, runReader, asks, local, ask)
import Text.TeXMath (readMathML, writeTeXMath)
import Data.Default (Default (..), def)
import Control.Monad.Reader (Reader,ask, asks, local, runReader)
isSpace :: Char -> Bool
isSpace ' ' = True
isSpace '\t' = True
isSpace '\n' = True
isSpace _ = False
-- | Convert HTML-formatted string to 'Pandoc' document.
readHtml :: ReaderOptions -- ^ Reader options
-> String -- ^ String to parse (assumes @'\n'@ line endings)
-> Pandoc
readHtml opts inp =
case flip runReader def $ runParserT parseDoc (HTMLState def{ stateOptions = opts } ) "source" tags of
case flip runReader def $ runParserT parseDoc (HTMLState def{ stateOptions = opts } []) "source" tags of
Left err' -> error $ "\nError at " ++ show err'
Right result -> result
where tags = canonicalizeTags $
where tags = stripPrefixes . canonicalizeTags $
parseTagsOptions parseOptions{ optTagPosition = True } inp
parseDoc = do
blocks <- (fixPlains False) . mconcat <$> manyTill block eof
meta <- stateMeta . parserState <$> getState
return $ Pandoc meta (B.toList blocks)
bs' <- replaceNotes (B.toList blocks)
return $ Pandoc meta bs'
replaceNotes :: [Block] -> TagParser [Block]
replaceNotes = walkM replaceNotes'
replaceNotes' :: Inline -> TagParser Inline
replaceNotes' (RawInline (Format "noteref") ref) = maybe (Str "") (Note . B.toList) . lookup ref <$> getNotes
where
getNotes = noteTable <$> getState
replaceNotes' x = return x
data HTMLState =
HTMLState
{ parserState :: ParserState
{ parserState :: ParserState,
noteTable :: [(String, Blocks)]
}
data HTMLLocal = HTMLLocal { quoteContext :: QuoteContext }
data HTMLLocal = HTMLLocal { quoteContext :: QuoteContext
, inChapter :: Bool -- ^ Set if in chapter section
}
setInChapter :: HTMLParser s a -> HTMLParser s a
setInChapter = local (\s -> s {inChapter = True})
type HTMLParser s = ParserT s HTMLState (Reader HTMLLocal)
@ -110,7 +126,11 @@ block = do
tr <- getOption readerTrace
pos <- getPosition
res <- choice
[ pPara
[ eSwitch
, eSection
, mempty <$ eFootnote
, mempty <$ eTOC
, pPara
, pHeader
, pBlockQuote
, pCodeBlock
@ -127,6 +147,64 @@ block = do
(take 60 $ show $ B.toList res)) (return ())
return res
namespaces :: [(String, TagParser Blocks)]
namespaces = [(mathMLNamespace, B.para <$> pMath True)]
mathMLNamespace :: String
mathMLNamespace = "http://www.w3.org/1998/Math/MathML"
eSwitch :: TagParser Blocks
eSwitch = try $ do
guardEnabled Ext_epub_html_exts
pSatisfy (~== TagOpen "switch" [])
cases <- getFirst . mconcat <$>
manyTill (First <$> (eCase <* skipMany pBlank) )
(lookAhead $ try $ pSatisfy (~== TagOpen "default" []))
skipMany pBlank
fallback <- pInTags "default" ( skipMany pBlank *> block <* skipMany pBlank )
skipMany pBlank
pSatisfy (~== TagClose "switch")
return (fromMaybe fallback cases)
eCase :: TagParser (Maybe Blocks)
eCase = do
skipMany pBlank
TagOpen _ attr <- lookAhead $ pSatisfy $ (~== TagOpen "case" [])
case (flip lookup namespaces) =<< lookup "required-namespace" attr of
Just p -> Just <$> (pInTags "case" (skipMany pBlank *> p <* skipMany pBlank))
Nothing -> Nothing <$ manyTill pAnyTag (pSatisfy (~== TagClose "case"))
eFootnote :: TagParser ()
eFootnote = try $ do
let notes = ["footnote", "rearnote"]
guardEnabled Ext_epub_html_exts
(TagOpen tag attr) <- lookAhead $ pAnyTag
guard (maybe False (flip elem notes) (lookup "type" attr))
let ident = fromMaybe "" (lookup "id" attr)
content <- pInTags tag block
addNote ident content
addNote :: String -> Blocks -> TagParser ()
addNote uid cont = updateState (\s -> s {noteTable = (uid, cont) : (noteTable s)})
eNoteref :: TagParser Inlines
eNoteref = try $ do
guardEnabled Ext_epub_html_exts
TagOpen tag attr <- lookAhead $ pAnyTag
guard (maybe False (== "noteref") (lookup "type" attr))
let ident = maybe "" (dropWhile (== '#')) (lookup "href" attr)
guard (not (null ident))
pInTags tag block
return $ B.rawInline "noteref" ident
-- Strip TOC if there is one, better to generate again
eTOC :: TagParser ()
eTOC = try $ do
guardEnabled Ext_epub_html_exts
(TagOpen tag attr) <- lookAhead $ pAnyTag
guard (maybe False (== "toc") (lookup "type" attr))
void (pInTags tag block)
pList :: TagParser Blocks
pList = pBulletList <|> pOrderedList <|> pDefinitionList
@ -139,9 +217,15 @@ pBulletList = try $ do
-- note: if they have an <ol> or <ul> not in scope of a <li>,
-- treat it as a list item, though it's not valid xhtml...
skipMany nonItem
items <- manyTill (pInTags "li" block <* skipMany nonItem) (pCloses "ul")
items <- manyTill (pListItem nonItem) (pCloses "ul")
return $ B.bulletList $ map (fixPlains True) items
pListItem :: TagParser a -> TagParser Blocks
pListItem nonItem = do
TagOpen _ attr <- lookAhead $ pSatisfy (~== TagOpen "li" [])
let liDiv = maybe mempty (\x -> B.divWith (x, [], []) mempty) (lookup "id" attr)
(liDiv <>) <$> pInTags "li" block <* skipMany nonItem
pOrderedList :: TagParser Blocks
pOrderedList = try $ do
TagOpen _ attribs <- pSatisfy (~== TagOpen "ol" [])
@ -167,7 +251,7 @@ pOrderedList = try $ do
-- note: if they have an <ol> or <ul> not in scope of a <li>,
-- treat it as a list item, though it's not valid xhtml...
skipMany nonItem
items <- manyTill (pInTags "li" block <* skipMany nonItem) (pCloses "ol")
items <- manyTill (pListItem nonItem) (pCloses "ol")
return $ B.orderedListWith (start, style, DefaultDelim) $ map (fixPlains True) items
pDefinitionList :: TagParser Blocks
@ -230,13 +314,35 @@ pHtmlBlock t = try $ do
contents <- manyTill pAnyTag (pSatisfy (~== TagClose t))
return $ renderTags' $ [open] ++ contents ++ [TagClose t]
-- Sets chapter context
eSection :: TagParser Blocks
eSection = try $ do
let matchChapter as = maybe False (isInfixOf "chapter") (lookup "type" as)
let sectTag = tagOpen (`elem` sectioningContent) matchChapter
TagOpen tag _ <- lookAhead $ pSatisfy sectTag
setInChapter (pInTags tag block)
headerLevel :: String -> TagParser Int
headerLevel tagtype = do
let level = read (drop 1 tagtype)
(try $ do
guardEnabled Ext_epub_html_exts
asks inChapter >>= guard
return (level - 1))
<|>
return level
pHeader :: TagParser Blocks
pHeader = try $ do
TagOpen tagtype attr <- pSatisfy $
tagOpen (`elem` ["h1","h2","h3","h4","h5","h6"])
(const True)
let bodyTitle = TagOpen tagtype attr ~== TagOpen "h1" [("class","title")]
let level = read (drop 1 tagtype)
level <- headerLevel tagtype
contents <- trimInlines . mconcat <$> manyTill inline (pCloses tagtype <|> eof)
let ident = fromMaybe "" $ lookup "id" attr
let classes = maybe [] words $ lookup "class" attr
@ -336,7 +442,8 @@ pCodeBlock = try $ do
inline :: TagParser Inlines
inline = choice
[ pTagText
[ eNoteref
, pTagText
, pQ
, pEmph
, pStrong
@ -348,6 +455,7 @@ inline = choice
, pImage
, pCode
, pSpan
, pMath False
, pRawHtmlInline
]
@ -416,12 +524,24 @@ pLineBreak = do
return B.linebreak
pLink :: TagParser Inlines
pLink = try $ do
pLink = pRelLink <|> pAnchor
pAnchor :: TagParser Inlines
pAnchor = try $ do
tag <- pSatisfy (tagOpenLit "a" (isJust . lookup "id"))
return $ B.spanWith (fromAttrib "id" tag , [], []) mempty
pRelLink :: TagParser Inlines
pRelLink = try $ do
tag <- pSatisfy (tagOpenLit "a" (isJust . lookup "href"))
let url = fromAttrib "href" tag
let title = fromAttrib "title" tag
let uid = fromAttrib "id" tag
let spanC = case uid of
[] -> id
s -> B.spanWith (s, [], [])
lab <- trimInlines . mconcat <$> manyTill inline (pCloses "a")
return $ B.link (escapeURI url) title lab
return $ spanC $ B.link (escapeURI url) title lab
pImage :: TagParser Inlines
pImage = do
@ -451,6 +571,22 @@ pRawHtmlInline = do
then return $ B.rawInline "html" $ renderTags' [result]
else return mempty
mathMLToTeXMath :: String -> Either String String
mathMLToTeXMath s = writeTeXMath <$> readMathML s
pMath :: Bool -> TagParser Inlines
pMath inCase = try $ do
open@(TagOpen _ attr) <- pSatisfy $ tagOpen (=="math") (const True)
unless (inCase) (guard (maybe False (== mathMLNamespace) (lookup "xmlns" attr)))
contents <- manyTill pAnyTag (pSatisfy (~== TagClose "math"))
let math = mathMLToTeXMath $
(renderTags $ [open] ++ contents ++ [TagClose "math"])
let constructor =
maybe B.math (\x -> if (x == "inline") then B.math else B.displayMath)
(lookup "display" attr)
return $ either (const mempty)
(\x -> if null x then mempty else constructor x) math
pInlinesInTags :: String -> (Inlines -> Inlines)
-> TagParser Inlines
pInlinesInTags tagtype f = extractSpaces f <$> pInTags tagtype inline
@ -620,8 +756,11 @@ blockDocBookTags = ["calloutlist", "bibliolist", "glosslist", "itemizedlist",
"classsynopsis", "blockquote", "epigraph", "msgset",
"sidebar", "title"]
epubTags :: [String]
epubTags = ["case", "switch", "default"]
blockTags :: [String]
blockTags = blockHtmlTags ++ blockDocBookTags
blockTags = blockHtmlTags ++ blockDocBookTags ++ epubTags
isInlineTag :: Tag String -> Bool
isInlineTag t = tagOpen isInlineTagName (const True) t ||
@ -720,9 +859,32 @@ htmlTag f = try $ do
mkAttr :: [(String, String)] -> Attr
mkAttr attr = (attribsId, attribsClasses, attribsKV)
where attribsId = fromMaybe "" $ lookup "id" attr
attribsClasses = words $ fromMaybe "" $ lookup "class" attr
attribsClasses = (words $ fromMaybe "" $ lookup "class" attr) ++ epubTypes
attribsKV = filter (\(k,_) -> k /= "class" && k /= "id") attr
epubTypes = words $ fromMaybe "" $ lookup "epub:type" attr
-- Strip namespace prefixes
stripPrefixes :: [Tag String] -> [Tag String]
stripPrefixes = map stripPrefix
stripPrefix :: Tag String -> Tag String
stripPrefix (TagOpen s as) =
TagOpen (stripPrefix' s) (map (stripPrefix' *** id) as)
stripPrefix (TagClose s) = TagClose (stripPrefix' s)
stripPrefix x = x
stripPrefix' :: String -> String
stripPrefix' s =
case span (/= ':') s of
(_, "") -> s
(_, (_:ts)) -> ts
isSpace :: Char -> Bool
isSpace ' ' = True
isSpace '\t' = True
isSpace '\n' = True
isSpace '\r' = True
isSpace _ = False
-- Instances
@ -736,17 +898,39 @@ instance HasReaderOptions HTMLState where
extractReaderOptions = extractReaderOptions . parserState
instance Default HTMLState where
def = HTMLState def
def = HTMLState def []
instance HasMeta HTMLState where
setMeta s b st = st {parserState = setMeta s b $ parserState st}
deleteMeta s st = st {parserState = deleteMeta s $ parserState st}
instance Default HTMLLocal where
def = HTMLLocal NoQuote
def = HTMLLocal NoQuote False
instance HasLastStrPosition HTMLState where
setLastStrPos s st = st {parserState = setLastStrPos s (parserState st)}
getLastStrPos = getLastStrPos . parserState
-- EPUB Specific
--
--
sectioningContent :: [String]
sectioningContent = ["article", "aside", "nav", "section"]
{-
groupingContent :: [String]
groupingContent = ["p", "hr", "pre", "blockquote", "ol"
, "ul", "li", "dl", "dt", "dt", "dd"
, "figure", "figcaption", "div", "main"]
types :: [(String, ([String], Int))]
types = -- Document divisions
map (\s -> (s, (["section", "body"], 0)))
["volume", "part", "chapter", "division"]
++ -- Document section and components
[
("abstract", ([], 0))]
-}

View file

@ -144,7 +144,12 @@ tests = [ testGroup "markdown"
]
, testGroup "txt2tags"
[ test "reader" ["-r", "t2t", "-w", "native"]
"txt2tags.t2t" "txt2tags.native"
"txt2tags.t2t" "txt2tags.native" ]
, testGroup "epub" [
test "features" ["-r", "epub", "-w", "native"]
"features.epub" "features.native"
, test "formatting" ["-r", "epub", "-w", "native"]
"formatting.epub" "formatting.native"
]
, testGroup "other writers" $ map (\f -> testGroup f $ writerTests f)
[ "opendocument" , "context" , "texinfo", "icml"

BIN
tests/features.epub Normal file

Binary file not shown.

482
tests/features.native Normal file
View file

@ -0,0 +1,482 @@
[Para [Span ("front.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"utf-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,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>"
,Header 2 ("",[],[]) [Str "Status",Space,Str "of",Space,Str "this",Space,Str "Document"]
,Para [Str "This",Space,Str "publication",Space,Str "is",Space,Str "currently",Space,Str "considered",Space,Span ("",["status"],[]) [Str "[UNDER",Space,Str "DEVELOPMENT]"],Space,Str "by",Space,Str "the",Space,Str "IDPF."]
,Para [Str "This",Space,Str "publication",Space,Str "is",Space,Str "part",Space,Str "of",Space,Str "version",Space,Span ("",["version"],[]) [Str "X.X"],Space,Str "of",Space,Str "the",Space,Str "EPUB",Space,Str "3.0",Space,Str "Compliance",Space,Str "Test",Space,Str "Suite",Space,Str "released",Space,Str "on",Space,RawInline (Format "html") "<time class=\"release\">",Str "TBD",RawInline (Format "html") "</time>",Str "."]
,Para [Str "Before",Space,Str "using",Space,Str "this",Space,Str "publication",Space,Str "to",Space,Str "evaluate",Space,Str "reading",Space,Str "systems,",Space,Str "testers",Space,Str "are",Space,Str "strongly",Space,Str "encouraged",Space,Str "to",Space,Str "verify",Space,Str "that",Space,Str "they",Space,Str "have",Space,Str "the",Space,Str "latest",Space,Str "release",Space,Str "by",Space,Str "checking",Space,Str "the",Space,Str "current",Space,Str "release",Space,Str "version",Space,Str "and",Space,Str "date",Space,Str "of",Space,Str "the",Space,Str "test",Space,Str "suite",Space,Str "at",Space,Link [Str "TBD"] ("","")]
,Para [Str "This",Space,Str "publication",Space,Str "is",Space,Str "one",Space,Str "of",Space,Str "several",Space,Str "that",Space,Str "currently",Space,Str "comprise",Space,Str "the",Space,Str "EPUB",Space,Str "3",Space,Str "conformance",Space,Str "test",Space,Str "suite",Space,Str "for",Space,Str "reflowable",Space,Str "content.",Space,Str "The",Space,Str "complete",Space,Str "test",Space,Str "suite",Space,Str "includes",Space,Str "all",Space,Str "of",Space,Str "the",Space,Str "following",Space,Str "publications:"]
,OrderedList (1,DefaultStyle,DefaultDelim)
[[Plain [Str "."]]]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section>"
,Header 2 ("",[],[]) [Str "About",Space,Str "this",Space,Str "Document"]
,Para [Str "This",Space,Str "document",Space,Str "focuses",Space,Str "on",Space,Str "human-evaluated",Space,Str "binary",Space,Str "(pass/fail)",Space,Str "tests",Space,Str "in",Space,Str "a",Space,Str "reflowable",Space,Str "context.",Space,Str "Tests",Space,Str "for",Space,Str "fixed-layout",Space,Str "content",Space,Str "and",Space,Str "other",Space,Str "individual",Space,Str "tests",Space,Str "that",Space,Str "require",Space,Str "a",Space,Str "dedicated",Space,Str "epub",Space,Str "file",Space,Str "are",Space,Str "available",Space,Str "in",Space,Str "additional",Space,Str "sibling",Space,Str "documents;",Space,Str "refer",Space,Str "to",Space,Str "the",Space,Link [Str "test",Space,Str "suite",Space,Str "wiki"] ("Overview",""),Space,Str "(",Code ("",[],[]) "https://github.com/mgylling/epub-testsuite/wiki/Overview",Str ")",Space,Str "for",Space,Str "additional",Space,Str "information."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section>"
,Header 2 ("",[],[]) [Str "Conventions"]
,Para [Str "The",Space,Str "following",Space,Str "conventions",Space,Str "are",Space,Str "used",Space,Str "throughout",Space,Str "the",Space,Str "document:"]
,DefinitionList
[([Str "1.",Space,Str "Locating",Space,Str "a",Space,Str "test"],
[[Div ("",["ctest"],[]) [Para [Str "Tests",Space,Str "for",Space,Emph [Str "required"],Space,Str "Reading",Space,Str "System",Space,Str "functionality",Space,Str "are",Space,Str "preceded",Space,Str "by",Space,Str "the",Space,Str "label:",Space,Span ("",["nature"],[("style","display: inline; font-size: 100%")]) [Str "[REQUIRED]"]]]
,Div ("",["otest"],[]) [Para [Str "Tests",Space,Str "for",Space,Emph [Str "optional"],Space,Str "Reading",Space,Str "System",Space,Str "functionality",Space,Str "are",Space,Str "preceded",Space,Str "by",Space,Str "the",Space,Str "label:",Space,Span ("",["nature"],[("style","display: inline; font-size: 100%")]) [Str "[OPTIONAL]"]]]]])
,([Str "2.",Space,Str "Performing",Space,Str "the",Space,Str "test"],
[[Plain [Str "Each",Space,Str "test",Space,Str "includes",Space,Str "a",Space,Str "description",Space,Str "of",Space,Str "its",Space,Str "purpose",Space,Str "followed",Space,Str "by",Space,Str "the",Space,Str "actual",Space,Strong [Str "test",Space,Str "statement,",Space,Str "which",Space,Str "can",Space,Str "always",Space,Str "be",Space,Str "evaluated",Space,Str "to",Space,Str "true",Space,Str "or",Space,Str "false"],Str ".",Space,Str "These",Space,Str "statements",Space,Str "typically",Space,Str "have",Space,Str "the",Space,Str "form:",Space,Str "\"If",Space,Str "[some",Space,Str "condition],",Space,Str "the",Space,Str "test",Space,Str "passes\"."]]])
,([Str "3.",Space,Str "Scoring",Space,Str "in",Space,Str "the",Space,Str "results",Space,Str "form"],
[[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-xhtml-001.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"utf-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,Header 1 ("",[],[]) [Str "Content",Space,Str "Documents:",Space,Str "XHTML"]
,Para [Str "This",Space,Str "section",Space,Str "contains",Space,Str "tests",Space,Str "for",Space,Str "static",Space,Str "XHTML",Space,Str "content."]
,Para [Span ("content-xhtml-002.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section id=\"iframe-010\" class=\"ctest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "iframe-010"],Space,Str "Inline",Space,Str "Frames"]
,Para [Str "Tests",Space,Str "whether",Space,Str "embedding",Space,Str "content",Space,Str "via",Space,Str "an",Space,Code ("",[],[]) "iframe",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<iframe src=\"content-xhtml-002-inset.xhtml\" width=\"300\" height=\"45\">",RawInline (Format "html") "</iframe>"]
,Para [Str "If",Space,Str "the",Space,Str "preceding",Space,Str "paragraph",Space,Str "reads",Space,Str "\"PASS\",",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,Para [Span ("content-images-001.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,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"] ("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"] ("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"] ("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-multimedia-001.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section>"
,RawBlock (Format "html") "<section>"
,Header 3 ("content-multimedia-001.xhtml#audio",[],[]) [Str "Audio"]
,RawBlock (Format "html") "<section id=\"audio-010\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "audio-010"],Space,Str "The",Space,Code ("",[],[]) "audio",Space,Str "element:",Space,Str "MP3"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Str "HTML5",Space,Code ("",[],[]) "audio",Space,Str "element",Space,Str "is",Space,Str "supported",Space,Str "using",Space,Code ("",[],[]) "MP3",Space,Str "audio."]
,Para [RawInline (Format "html") "<audio controls src=\"../audio/allison64.mp3\">",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "audio",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</audio>"]
,Para [Str "If",Space,Str "the",Space,Str "preceding",Space,Str "audio",Space,Str "clip",Space,Str "can",Space,Str "be",Space,Str "played",Space,Str "(a",Space,Str "woman's",Space,Str "voice",Space,Str "will",Space,Str "be",Space,Str "heard,",Space,Str "beginning",Space,Str "\"a",Space,Str "crime",Space,Str "to",Space,Str "sink",Space,Str "your",Space,Str "teeth",Space,Str "into\"),",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"audio-020\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "audio-020"],Space,Str "The",Space,Code ("",[],[]) "audio",Space,Str "element:",Space,Str "MP4",Space,Str "AAC",Space,Str "LC"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Str "HTML5",Space,Code ("",[],[]) "audio",Space,Str "element",Space,Str "is",Space,Str "supported",Space,Str "using",Space,Code ("",[],[]) "AAC LC",Space,Str "audio",Space,Str "in",Space,Str "an",Space,Code ("",[],[]) "MP4",Space,Str "container."]
,Para [RawInline (Format "html") "<audio controls src=\"../audio/allison64.mp4\">",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "audio",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</audio>"]
,Para [Str "If",Space,Str "the",Space,Str "preceding",Space,Str "audio",Space,Str "clip",Space,Str "can",Space,Str "be",Space,Str "played",Space,Str "(a",Space,Str "woman's",Space,Str "voice",Space,Str "will",Space,Str "be",Space,Str "heard,",Space,Str "beginning",Space,Str "\"a",Space,Str "crime",Space,Str "to",Space,Str "sink",Space,Str "your",Space,Str "teeth",Space,Str "into\"),",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"audio-030\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "audio-030"],Space,Str "The",Space,Code ("",[],[]) "audio",Space,Str "element:",Space,Code ("",[],[]) "source",Space,Str "elements"]
,Para [Str "Tests",Space,Str "whether",Space,Str "media",Space,Str "specified",Space,Str "via",Space,Code ("",[],[]) "source",Space,Str "elements",Space,Str "is",Space,Str "recognized:"]
,Para [RawInline (Format "html") "<audio controls>",Space,RawInline (Format "html") "<source src=\"../audio/allison64.mp4\" type=\"audio/mp4\">",RawInline (Format "html") "</source>",Space,RawInline (Format "html") "<source src=\"../audio/allison64.mp3\" type=\"audio/mp3\">",RawInline (Format "html") "</source>",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "audio",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</audio>"]
,Para [Str "If",Space,Str "the",Space,Str "preceding",Space,Str "audio",Space,Str "clip",Space,Str "can",Space,Str "be",Space,Str "played",Space,Str "(a",Space,Str "woman's",Space,Str "voice",Space,Str "will",Space,Str "be",Space,Str "heard,",Space,Str "beginning",Space,Str "\"a",Space,Str "crime",Space,Str "to",Space,Str "sink",Space,Str "your",Space,Str "teeth",Space,Str "into\"),",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,Para [Span ("content-multimedia-002.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section>"
,Header 3 ("content-multimedia-002.xhtml#video",[],[]) [Str "Video"]
,RawBlock (Format "html") "<section id=\"video-010\" class=\"otest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "video-010"],Space,Str "The",Space,Code ("",[],[]) "video",Space,Str "element:",Space,Str "VP8"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Str "HTML5",Space,Code ("",[],[]) "video",Space,Str "element",Space,Str "is",Space,Str "supported",Space,Str "using",Space,Code ("",[],[]) "WebM",Space,Str "video",Space,Str "(VP8",Space,Str "video",Space,Str "with",Space,Str "Vorbis",Space,Str "audio)."]
,Para [RawInline (Format "html") "<video controls src=\"../video/screencast.webm\" width=\"278\" height=\"240\">",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "video",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</video>"]
,Para [Str "If",Space,Str "the",Space,Str "preceding",Space,Str "video",Space,Str "clip",Space,Str "can",Space,Str "be",Space,Str "played",Space,Str "(a",Space,Str "man's",Space,Str "voice",Space,Str "will",Space,Str "be",Space,Str "heard,",Space,Str "beginning",Space,Str "\"Hi",Space,Str "there,",Space,Str "I",Space,Str "quickly",Space,Str "want",Space,Str "to",Space,Str "show",Space,Str "you\"),",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"video-020\" class=\"otest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "video-020"],Space,Str "The",Space,Code ("",[],[]) "video",Space,Str "element:",Space,Str "H.264"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Str "HTML5",Space,Code ("",[],[]) "video",Space,Str "element",Space,Str "is",Space,Str "supported",Space,Str "using",Space,Code ("",[],[]) "MP4",Space,Str "video",Space,Str "(H.264",Space,Str "video",Space,Str "with",Space,Str "AAC-LC",Space,Str "audio)."]
,Para [RawInline (Format "html") "<video controls src=\"../video/screencast.mp4\" width=\"278\" height=\"240\">",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "video",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</video>"]
,Para [Str "If",Space,Str "the",Space,Str "preceding",Space,Str "video",Space,Str "clip",Space,Str "can",Space,Str "be",Space,Str "played",Space,Str "(a",Space,Str "man's",Space,Str "voice",Space,Str "will",Space,Str "be",Space,Str "heard,",Space,Str "beginning",Space,Str "\"Hi",Space,Str "there,",Space,Str "I",Space,Str "quickly",Space,Str "want",Space,Str "to",Space,Str "show",Space,Str "you\"),",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"video-030\" class=\"otest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "video-030"],Space,Str "The",Space,Code ("",[],[]) "video",Space,Str "element:",Space,Code ("",[],[]) "source",Space,Str "elements"]
,Para [Str "Tests",Space,Str "whether",Space,Str "media",Space,Str "specified",Space,Str "via",Space,Code ("",[],[]) "source",Space,Str "elements",Space,Str "is",Space,Str "recognized:"]
,Para [RawInline (Format "html") "<video controls width=\"278\" height=\"240\" poster=\"../img/Skype_logo.png\">",Space,RawInline (Format "html") "<source src=\"../video/screencast.mp4\" type=\"video/mp4\">",RawInline (Format "html") "</source>",Space,RawInline (Format "html") "<source src=\"../video/screencast.webm\" type=\"video/webm\">",RawInline (Format "html") "</source>",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "video",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</video>"]
,Para [Str "If",Space,Str "the",Space,Str "preceding",Space,Str "video",Space,Str "clip",Space,Str "can",Space,Str "be",Space,Str "played",Space,Str "(a",Space,Str "man's",Space,Str "voice",Space,Str "will",Space,Str "be",Space,Str "heard,",Space,Str "beginning",Space,Str "\"Hi",Space,Str "there,",Space,Str "I",Space,Str "quickly",Space,Str "want",Space,Str "to",Space,Str "show",Space,Str "you\"),",Space,Str "the",Space,Str "test",Space,Str "passes."]
,Para [Str "This",Space,Str "test",Space,Str "will",Space,Str "fail",Space,Str "if",Space,Str "neither",Space,Str "H.264",Space,Str "nor",Space,Str "VP8",Space,Str "are",Space,Str "supported,",Space,Str "regardless",Space,Str "of",Space,Str "support",Space,Str "for",Space,Str "the",Space,Code ("",[],[]) "source",Space,Str "element.",Space,Str "Other",Space,Str "codecs",Space,Str "must",Space,Str "be",Space,Str "tested",Space,Str "manually."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"video-040\" class=\"otest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "video-040"],Space,Str "The",Space,Code ("",[],[]) "video",Space,Str "element:",Space,Str "Poster",Space,Str "Images"]
,Para [Str "Tests",Space,Str "whether",Space,Str "poster",Space,Str "images",Space,Str "are",Space,Str "supported",Space,Str "the",Space,Str "HTML5",Space,Code ("",[],[]) "video",Space,Str "element:"]
,Para [RawInline (Format "html") "<video controls width=\"278\" height=\"240\" poster=\"../img/Skype_logo.png\">",Space,RawInline (Format "html") "<source src=\"../video/screencast.mp4\" type=\"video/mp4\">",RawInline (Format "html") "</source>",Space,RawInline (Format "html") "<source src=\"../video/screencast.webm\" type=\"video/webm\">",RawInline (Format "html") "</source>",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "video",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</video>"]
,Para [Str "If",Space,Str "the",Space,Str "Skype",Space,Str "logo",Space,Str "appears",Space,Str "in",Space,Str "the",Space,Str "video",Space,Str "area,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"video-050\" class=\"otest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "video-050"],Space,Str "The",Space,Code ("",[],[]) "video",Space,Str "element:",Space,Str "Captions",Space,Str "(WebVTT)"]
,Para [Str "Tests",Space,Str "whether",Space,Str "WebVTT",Space,Str "captions",Space,Str "are",Space,Str "supported",Space,Str "in",Space,Str "the",Space,Str "HTML5",Space,Code ("",[],[]) "video",Space,Str "element:"]
,Para [RawInline (Format "html") "<video controls width=\"278\" height=\"240\">",Space,RawInline (Format "html") "<source src=\"../video/screencast.mp4\" type=\"video/mp4\">",RawInline (Format "html") "</source>",Space,RawInline (Format "html") "<source src=\"../video/screencast.webm\" type=\"video/webm\">",RawInline (Format "html") "</source>",Space,RawInline (Format "html") "<track kind=\"captions\" src=\"../video/tracks/screencast.vtt\" srclang=\"en\" label=\"English\" default=\"default\">",RawInline (Format "html") "</track>",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "video",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</video>"]
,Para [Str "If",Space,Str "captions",Space,Str "appear",Space,Str "during",Space,Str "the",Space,Str "first",Space,Str "10s",Space,Str "of",Space,Str "video",Space,Str "playback,",Space,Str "or",Space,Str "can",Space,Str "be",Space,Str "turned",Space,Str "on",Space,Str "from",Space,Str "the",Space,Str "player",Space,Str "interface,",Space,Str "then",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"video-060\" class=\"otest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "video-060"],Space,Str "The",Space,Code ("",[],[]) "video",Space,Str "element:",Space,Str "Captions",Space,Str "(TTML)"]
,Para [Str "Tests",Space,Str "whether",Space,Str "TTML",Space,Str "captions",Space,Str "are",Space,Str "supported",Space,Str "in",Space,Str "the",Space,Str "HTML5",Space,Code ("",[],[]) "video",Space,Str "element:"]
,Para [RawInline (Format "html") "<video controls width=\"278\" height=\"240\">",Space,RawInline (Format "html") "<source src=\"../video/screencast.mp4\" type=\"video/mp4\">",RawInline (Format "html") "</source>",Space,RawInline (Format "html") "<source src=\"../video/screencast.webm\" type=\"video/webm\">",RawInline (Format "html") "</source>",Space,RawInline (Format "html") "<track kind=\"captions\" src=\"../video/tracks/screencast.ttml\" srclang=\"en\" label=\"English\" default=\"default\">",RawInline (Format "html") "</track>",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "video",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</video>"]
,Para [Str "If",Space,Str "captions",Space,Str "appear",Space,Str "during",Space,Str "the",Space,Str "first",Space,Str "10s",Space,Str "of",Space,Str "video",Space,Str "playback,",Space,Str "or",Space,Str "can",Space,Str "be",Space,Str "turned",Space,Str "on",Space,Str "from",Space,Str "the",Space,Str "player",Space,Str "interface,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"video-070\" class=\"otest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "video-070"],Space,Str "The",Space,Code ("",[],[]) "video",Space,Str "element:",Space,Str "Subtitles",Space,Str "(WebVTT)"]
,Para [Str "Tests",Space,Str "whether",Space,Str "WebVTT",Space,Str "subtitles",Space,Str "are",Space,Str "supported",Space,Str "in",Space,Str "the",Space,Str "HTML5",Space,Code ("",[],[]) "video",Space,Str "element:"]
,Para [RawInline (Format "html") "<video controls width=\"278\" height=\"240\">",Space,RawInline (Format "html") "<source src=\"../video/screencast.mp4\" type=\"video/mp4\">",RawInline (Format "html") "</source>",Space,RawInline (Format "html") "<source src=\"../video/screencast.webm\" type=\"video/webm\">",RawInline (Format "html") "</source>",Space,RawInline (Format "html") "<track kind=\"subtitles\" src=\"../video/tracks/screencast.vtt\" srclang=\"en\" label=\"English\" default=\"default\">",RawInline (Format "html") "</track>",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "video",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</video>"]
,Para [Str "If",Space,Str "subtitles",Space,Str "appear",Space,Str "during",Space,Str "the",Space,Str "first",Space,Str "10s",Space,Str "of",Space,Str "video",Space,Str "playback,",Space,Str "or",Space,Str "can",Space,Str "be",Space,Str "turned",Space,Str "on",Space,Str "from",Space,Str "the",Space,Str "player",Space,Str "interface,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"video-080\" class=\"otest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "video-080"],Space,Str "The",Space,Code ("",[],[]) "video",Space,Str "element:",Space,Str "Subtitles",Space,Str "(TTML)"]
,Para [Str "Tests",Space,Str "whether",Space,Str "TTML",Space,Str "subtitles",Space,Str "are",Space,Str "supported",Space,Str "in",Space,Str "the",Space,Str "HTML5",Space,Code ("",[],[]) "video",Space,Str "element:"]
,Para [RawInline (Format "html") "<video controls width=\"278\" height=\"240\">",Space,RawInline (Format "html") "<source src=\"../video/screencast.mp4\" type=\"video/mp4\">",RawInline (Format "html") "</source>",Space,RawInline (Format "html") "<source src=\"../video/screencast.webm\" type=\"video/webm\">",RawInline (Format "html") "</source>",Space,RawInline (Format "html") "<track kind=\"subtitles\" src=\"../video/tracks/screencast.ttml\" srclang=\"en\" label=\"English\" default=\"default\">",RawInline (Format "html") "</track>",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "video",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</video>"]
,Para [Str "If",Space,Str "subtitles",Space,Str "appear",Space,Str "during",Space,Str "the",Space,Str "first",Space,Str "10s",Space,Str "of",Space,Str "video",Space,Str "playback,",Space,Str "or",Space,Str "can",Space,Str "be",Space,Str "turned",Space,Str "on",Space,Str "from",Space,Str "the",Space,Str "player",Space,Str "interface,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,Para [Span ("content-multimedia-003.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section>"
,Header 3 ("content-multimedia-003.xhtml#trigger",[],[]) [Code ("",[],[]) "epub:trigger"]
,RawBlock (Format "html") "<section id=\"trigger-010\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "trigger-010"],Space,Str "The",Space,Code ("",[],[]) "trigger",Space,Str "element:",Space,Str "play"]
,Para [Str "Tests",Space,Str "whether",Space,Str "playback",Space,Str "of",Space,Str "multimedia",Space,Str "content",Space,Str "by",Space,Code ("",[],[]) "epub:trigger",Space,Str "elements",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<audio controls src=\"../audio/allison64.mp3\" id=\"audio01\">",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "audio",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</audio>",Space,RawInline (Format "html") "<trigger observer=\"play-button\" event=\"click\" action=\"play\" ref=\"audio01\">",RawInline (Format "html") "</trigger>"]
,Div ("",["trigger-ctrl"],[]) [Plain [Span ("content-multimedia-003.xhtml#play-button",[],[("aria-controls","audio01"),("role","button"),("tabindex","0")]) [Str "play"],LineBreak]]
,Para [Str "If",Space,Str "the",Space,Str "\"play\"",Space,Str "button",Space,Str "initiates",Space,Str "playback",Space,Str "of",Space,Str "the",Space,Str "audio",Space,Str "clip",Space,Str "from",Space,Str "00:00:00,",Space,Str "including",Space,Str "when",Space,Str "pressed",Space,Str "during",Space,Str "playback",Space,Str "or",Space,Str "after",Space,Str "pausing,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"trigger-020\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "trigger-020"],Space,Str "The",Space,Code ("",[],[]) "trigger",Space,Str "element:",Space,Str "pause/resume"]
,Para [Str "Tests",Space,Str "whether",Space,Str "pausing",Space,Str "and",Space,Str "resumption",Space,Str "of",Space,Str "multimedia",Space,Str "content",Space,Str "by",Space,Code ("",[],[]) "epub:trigger",Space,Str "elements",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<audio controls src=\"../audio/allison64.mp3\" id=\"audio02\">",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "audio",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</audio>",Space,RawInline (Format "html") "<trigger observer=\"pause-button\" event=\"click\" action=\"pause\" ref=\"audio02\">",RawInline (Format "html") "</trigger>",Space,RawInline (Format "html") "<trigger observer=\"resume-button\" event=\"click\" action=\"resume\" ref=\"audio02\">",RawInline (Format "html") "</trigger>"]
,Div ("",["trigger-ctrl"],[]) [Plain [Span ("content-multimedia-003.xhtml#resume-button",[],[("aria-controls","audio02"),("role","button"),("tabindex","0")]) [Str "resume"],Space,Span ("content-multimedia-003.xhtml#pause-button",[],[("aria-controls","audio02"),("role","button"),("tabindex","0")]) [Str "pause"],LineBreak]]
,Para [Str "If",Space,Str "the",Space,Str "\"resume\"",Space,Str "button",Space,Str "(re)starts",Space,Str "playback",Space,Str "of",Space,Str "the",Space,Str "audio",Space,Str "clip",Space,Str "and",Space,Str "the",Space,Str "\"pause\"",Space,Str "button",Space,Str "halts",Space,Str "it,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"trigger-030\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "trigger-030"],Space,Str "The",Space,Code ("",[],[]) "trigger",Space,Str "element:",Space,Str "mute/unmute"]
,Para [Str "Tests",Space,Str "whether",Space,Str "muting",Space,Str "and",Space,Str "unmuting",Space,Str "of",Space,Str "multimedia",Space,Str "content",Space,Str "by",Space,Code ("",[],[]) "epub:trigger",Space,Str "elements",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<audio controls src=\"../audio/allison64.mp3\" id=\"audio03\">",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "audio",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</audio>",Space,RawInline (Format "html") "<trigger observer=\"mute-button\" event=\"click\" action=\"mute\" ref=\"audio03\">",RawInline (Format "html") "</trigger>",Space,RawInline (Format "html") "<trigger observer=\"unmute-button\" event=\"click\" action=\"unmute\" ref=\"audio03\">",RawInline (Format "html") "</trigger>"]
,Div ("",["trigger-ctrl"],[]) [Plain [Span ("content-multimedia-003.xhtml#mute-button",[],[("aria-controls","audio03"),("role","button"),("tabindex","0")]) [Str "mute"],Space,Span ("content-multimedia-003.xhtml#unmute-button",[],[("aria-controls","audio03"),("role","button"),("tabindex","0")]) [Str "unmute"],LineBreak]]
,Para [Str "After",Space,Str "initiating",Space,Str "playback",Space,Str "of",Space,Str "the",Space,Str "audio",Space,Str "clip,",Space,Str "if",Space,Str "the",Space,Str "\"mute\"",Space,Str "button",Space,Str "silences",Space,Str "the",Space,Str "audio",Space,Str "track",Space,Str "and",Space,Str "\"unmute\"",Space,Str "re-enables",Space,Str "it",Space,Str "(at",Space,Str "the",Space,Str "same",Space,Str "volume",Space,Str "as",Space,Str "before),",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"trigger-040\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "trigger-040"],Space,Str "The",Space,Code ("",[],[]) "trigger",Space,Str "element:",Space,Str "hide/show"]
,Para [Str "Tests",Space,Str "whether",Space,Str "content",Space,Str "can",Space,Str "be",Space,Str "hidden",Space,Str "and",Space,Str "revealed",Space,Str "by",Space,Code ("",[],[]) "epub:trigger",Space,Str "elements."]
,Para [RawInline (Format "html") "<audio controls src=\"../audio/allison64.mp3\" id=\"audio04\">",Space,Str "If",Space,Str "this",Space,Str "text",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "audio",Space,Str "element",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "and",Space,Str "the",Space,Str "test",Space,Str "fails.",Space,RawInline (Format "html") "</audio>",Space,RawInline (Format "html") "<trigger observer=\"hide-button\" event=\"click\" action=\"hide\" ref=\"audio04\">",RawInline (Format "html") "</trigger>",Space,RawInline (Format "html") "<trigger observer=\"show-button\" event=\"click\" action=\"show\" ref=\"audio04\">",RawInline (Format "html") "</trigger>"]
,Div ("",["trigger-ctrl"],[]) [Plain [Span ("content-multimedia-003.xhtml#hide-button",[],[("aria-controls","audio04"),("role","button"),("tabindex","0")]) [Str "hide"],Space,Span ("content-multimedia-003.xhtml#show-button",[],[("aria-controls","audio04"),("role","button"),("tabindex","0")]) [Str "show"],LineBreak]]
,Para [Str "If",Space,Str "the",Space,Str "\"hide\"",Space,Str "button",Space,Str "hides",Space,Str "the",Space,Str "audio",Space,Str "player",Space,Str "and",Space,Str "the",Space,Str "\"show\"",Space,Str "button",Space,Str "reveals",Space,Str "it,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,Para [Span ("content-ns-001.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section>"
,Header 2 ("content-ns-001.xhtml#ns",[],[]) [Str "Namespace",Space,Str "Support"]
,RawBlock (Format "html") "<section id=\"namespace-010\" class=\"ctest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "namespace-010"],Space,Str "Prefixes"]
,Para [Str "Tests",Space,Str "that",Space,Str "namespace",Space,Str "prefix",Space,Str "support",Space,Str "is",Space,Str "not",Space,Str "hard-coded",Space,Str "into",Space,Str "the",Space,Str "application."]
,Para [RawInline (Format "html") "<svg width=\"100\" height=\"100\" version=\"1.1\">",Space,RawInline (Format "html") "<circle cx=\"50\" cy=\"50\" r=\"40\" style=\"fill:#000\">",RawInline (Format "html") "</circle>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "a",Space,Str "black",Space,Str "circle",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 "SVG",Space,Str "is",Space,Str "not",Space,Str "supported,",Space,Str "this",Space,Str "test",Space,Str "will",Space,Str "fail",Space,Str "regardless",Space,Str "of",Space,Str "actual",Space,Str "namespace",Space,Str "prefix",Space,Str "support.",Space,Str "Prefix",Space,Str "support",Space,Str "will",Space,Str "need",Space,Str "to",Space,Str "be",Space,Str "manually",Space,Str "tested",Space,Str "against",Space,Str "a",Space,Str "supported",Space,Str "namespace."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,Para [Span ("content-mathml-001.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"utf-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section>"
,Header 2 ("content-mathml-001.xhtml#mathml",[],[]) [Str "MathML"]
,RawBlock (Format "html") "<section id=\"mathml-010\" class=\"ctest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "mathml-010"],Space,Str "Rendering"]
,Para [Str "Tests",Space,Str "whether",Space,Str "MathML",Space,Str "equation",Space,Str "rendering",Space,Str "is",Space,Str "supported."]
,Para [Math DisplayMath "\\int_{-\\mathrm{\8734}}^{\\mathrm{\8734}}e^{-x^{2}} dx=\\sqrt{\\pi}",Space,Math DisplayMath "\\underset{n=1}{\\overset{\\mathrm{\8734}}{\\sum}}\\frac{1}{n^{2}}=\\frac{\\pi^{2}}{6}",Space,Math DisplayMath "x=\\frac{-b\\pm\\sqrt{b^{2}-4ac}}{2a}"]
,Para [Str "If",Space,Str "the",Space,Str "preceding",Space,Str "equations",Space,Str "are",Space,Str "not",Space,Str "presented",Space,Str "as",Space,Str "linear",Space,Str "text",Space,Str "(e.g.,",Space,Str "x=-b\177b2-4ac2a),",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"mathml-020\" class=\"otest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "mathml-020"],Space,Str "CSS",Space,Str "Styling",Space,Str "of",Space,Str "the",Space,Code ("",[],[]) "math",Space,Str "element"]
,Para [Str "Tests",Space,Str "whether",Space,Str "basic",Space,Str "CSS",Space,Str "styling",Space,Str "of",Space,Str "MathML",Space,Str "is",Space,Str "supported",Space,Str "on",Space,Str "the",Space,Code ("",[],[]) "math",Space,Str "element."]
,Para [Math InlineMath "{2x}{+y-z}"]
,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "equation",Space,Str "has",Space,Str "a",Space,Str "yellow",Space,Str "background",Space,Str "and",Space,Str "a",Space,Str "dashed",Space,Str "border."]
,Para [Str "If",Space,Str "the",Space,Str "reading",Space,Str "system",Space,Str "does",Space,Str "not",Space,Str "have",Space,Str "a",Space,Str "viewport,",Space,Str "or",Space,Str "does",Space,Str "not",Space,Str "support",Space,Str "CSS",Space,Str "styles,",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 id=\"mathml-021\" class=\"otest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "mathml-021"],Space,Str "CSS",Space,Str "Styling",Space,Str "of",Space,Str "the",Space,Code ("",[],[]) "mo",Space,Str "element"]
,Para [Str "Tests",Space,Str "whether",Space,Str "basic",Space,Str "CSS",Space,Str "styling",Space,Str "of",Space,Str "MathML",Space,Str "is",Space,Str "supported",Space,Str "on",Space,Str "the",Space,Code ("",[],[]) "mo",Space,Str "element."]
,Para [Math InlineMath "{2x}{+y-z}"]
,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "operators",Space,Str "are",Space,Str "enlarged",Space,Str "relative",Space,Str "to",Space,Str "the",Space,Str "other",Space,Str "symbols",Space,Str "and",Space,Str "numbers."]
,Para [Str "If",Space,Str "the",Space,Str "reading",Space,Str "system",Space,Str "does",Space,Str "not",Space,Str "have",Space,Str "a",Space,Str "viewport,",Space,Str "or",Space,Str "does",Space,Str "not",Space,Str "support",Space,Str "CSS",Space,Str "styles,",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 id=\"mathml-022\" class=\"otest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "mathml-022"],Space,Str "CSS",Space,Str "Styling",Space,Str "of",Space,Str "the",Space,Code ("",[],[]) "mi",Space,Str "element"]
,Para [Str "Tests",Space,Str "whether",Space,Str "basic",Space,Str "CSS",Space,Str "styling",Space,Str "of",Space,Str "MathML",Space,Str "is",Space,Str "supported",Space,Str "on",Space,Str "the",Space,Code ("",[],[]) "mi",Space,Str "element."]
,Para [Math InlineMath "{2x}{+y-z}"]
,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "identifiers",Space,Str "are",Space,Str "bolded",Space,Str "and",Space,Str "blue."]
,Para [Str "If",Space,Str "the",Space,Str "reading",Space,Str "system",Space,Str "does",Space,Str "not",Space,Str "have",Space,Str "a",Space,Str "viewport,",Space,Str "or",Space,Str "does",Space,Str "not",Space,Str "support",Space,Str "CSS",Space,Str "styles,",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 id=\"mathml-023\" class=\"otest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "mathml-023"],Space,Str "CSS",Space,Str "Styling",Space,Str "of",Space,Str "the",Space,Code ("",[],[]) "mn",Space,Str "element"]
,Para [Str "Tests",Space,Str "whether",Space,Str "basic",Space,Str "CSS",Space,Str "styling",Space,Str "of",Space,Str "MathML",Space,Str "is",Space,Str "supported",Space,Str "on",Space,Str "the",Space,Code ("",[],[]) "mn",Space,Str "element."]
,Para [Math InlineMath "{2x}{+y-z}"]
,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "number",Space,Str "2",Space,Str "is",Space,Str "italicized",Space,Str "and",Space,Str "blue."]
,Para [Str "If",Space,Str "the",Space,Str "reading",Space,Str "system",Space,Str "does",Space,Str "not",Space,Str "have",Space,Str "a",Space,Str "viewport,",Space,Str "or",Space,Str "does",Space,Str "not",Space,Str "support",Space,Str "CSS",Space,Str "styles,",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 id=\"mathml-024\" class=\"ctest\">"
,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{\\mathrm{complex\\ number}}{\\overbrace{\\underset{\\mathrm{real}}{\\underbrace{\\qquad a\\qquad}}+\\underset{\\mathrm{imaginary}}{\\underbrace{\\quad bi\\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."] ("complex_number.png",""),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(\\operatorname{\\mathcal{L}}\\right) & \\longrightarrow & \\operatorname{non}\\left(\\operatorname{\\mathcal{K}}\\right) & \\longrightarrow & \\operatorname{cof}\\left(\\operatorname{\\mathcal{K}}\\right) & \\longrightarrow & \\operatorname{cof}\\left(\\operatorname{\\mathcal{L}}\\right) & \\longrightarrow & 2^{\\aleph_{0}} \\\\\n & \\uparrow & & \\uparrow & & \\uparrow & & \\uparrow & & \\\\\n & \\operatorname{\\mathfrak{b}} & \\longrightarrow & \\operatorname{\\mathfrak{d}} & & & & & & \\\\\n & \\uparrow & & \\uparrow & & & & & & \\\\\n\\aleph_{1} & \\longrightarrow & \\operatorname{add}\\left(\\operatorname{\\mathcal{L}}\\right) & \\longrightarrow & \\operatorname{add}\\left(\\operatorname{\\mathcal{K}}\\right) & \\longrightarrow & \\operatorname{cov}\\left(\\operatorname{\\mathcal{K}}\\right) & \\longrightarrow & \\operatorname{non}\\left(\\operatorname{\\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."] ("cichons_diagram.png",""),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"]
,Para [Str "Tests",Space,Str "whether",Space,Str "right-to-left",Space,Str "and",Space,Str "Arabic",Space,Str "alphabets",Space,Str "are",Space,Str "supported."]
,Para [Math DisplayMath "{d{\\left(s\\right)}}={\\left\\{\\begin{array}{ll}\n{\\underset{\\operatorname{\\lbrack?\\rbrack}=1}{\\overset{S}{\\sum}}s^{\\operatorname{\\lbrack?\\rbrack}}} & {\\mathrm{\1573\1584\1575\1603\1575\1606}s>0} \\\\\n{\\int_{1}^{S}{s^{\\operatorname{\\lbrack?\\rbrack}}\\operatorname{}s}} & {\\mathrm{\1573\1584\1575\1603\1575\1606}s\\in m} \\\\\n{T\\pi} & {\\mathrm{\1594\1610\1585\1584\1604\1603}{\\left(\\mathrm{\1605\1593}\\pi\\simeq 3,141\\right)}} \\\\\n\\end{array}\\right.}"]
,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 "piecewise",Space,Str "defined",Space,Str "function",Space,Str "in",Space,Str "Maghreb-style",Space,Str "notation"] ("Maghreb1.png",""),Str "."]
,RawBlock (Format "html") "</section>"
,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"] ("ElementaryMathExample.png",""),Str "."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"mathml-028\" class=\"ctest\">"
,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "mathml-028"],Str "Multiscripts,",Space,Str "Greek",Space,Str "and",Space,Str "Gothic",Space,Str "alphabets"]
,Para [Str "Tests",Space,Str "whether",Space,Code ("",[],[]) "mmultiscript",Space,Str "elements",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "Greek",Space,Str "and",Space,Str "Gothic",Space,Str "alphabets",Space,Str "are",Space,Str "supported."]
,Para [Math DisplayMath "\\underset{}{\\overset{}{}}"]
,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 "large",Space,Str "capital",Space,Str "Pi",Space,Str "with",Space,Str "Gothic",Space,Str "characters",Space,Str "as",Space,Str "multiscripts",Space,Str "which",Space,Str "in",Space,Str "turn",Space,Str "have",Space,Str "Greek",Space,Str "multiscripts"] ("multiscripts_and_greek_alphabet.png",""),Str "."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,Para [Span ("content-svg-001.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section id=\"svg\">"
,Header 2 ("",[],[]) [Str "SVG"]
,RawBlock (Format "html") "<section id=\"svg-shapes\">"
,Header 3 ("",[],[]) [Str "Shapes"]
,RawBlock (Format "html") "<section id=\"svg-010\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-010"],Space,Str "Circle"]
,Para [Str "Tests",Space,Str "whether",Space,Str "simple",Space,Str "vector",Space,Str "shapes",Space,Str "are",Space,Str "supported",Space,Str "by",Space,Str "drawing",Space,Str "a",Space,Str "circle."]
,Para [RawInline (Format "html") "<svg width=\"100\" height=\"100\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\">",Space,RawInline (Format "html") "<circle cx=\"50\" cy=\"50\" r=\"40\" style=\"fill:#000\">",RawInline (Format "html") "</circle>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "a",Space,Str "black",Space,Str "circle",Space,Str "is",Space,Str "rendered",Space,Str "before",Space,Str "this",Space,Str "paragraph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-020\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-020"],Space,Str "Transformation"]
,Para [Str "Tests",Space,Str "whether",Space,Str "simple",Space,Str "vector",Space,Str "shape",Space,Str "transformations",Space,Str "are",Space,Str "supported",Space,Str "by",Space,Str "transforming",Space,Str "a",Space,Str "square",Space,Str "into",Space,Str "a",Space,Str "diamond."]
,Para [RawInline (Format "html") "<svg width=\"100\" height=\"100\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\">",Space,RawInline (Format "html") "<rect x=\"25\" y=\"25\" width=\"50\" height=\"50\" transform=\"translate(50 12.5) scale(1 0.5) rotate(45)\">",RawInline (Format "html") "</rect>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "a",Space,Str "black",Space,Str "diamond",Space,Str "is",Space,Str "rendered",Space,Str "before",Space,Str "this",Space,Str "paragraph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,Para [Span ("content-svg-002.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section id=\"svg-text\">"
,Header 3 ("",[],[]) [Str "Text",Space,Str "content"]
,RawBlock (Format "html") "<section id=\"svg-text-styling\">"
,Header 4 ("",[],[]) [Str "Styling"]
,RawBlock (Format "html") "<section id=\"svg-110\" class=\"ctest\">"
,Header 5 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-110"],Space,Code ("",[],[]) "letter-spacing"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "letter-spacing",Space,Str "attribute",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"100\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\">",Space,RawInline (Format "html") "<g>",Space,RawInline (Format "html") "<text x=\"3\" y=\"20\" letter-spacing=\"-1\">",Str "letter-spacing",Space,Str "set",Space,Str "to",Space,Str "-1",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text x=\"3\" y=\"50\">",Str "default",Space,Str "letter-spacing",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text x=\"3\" y=\"80\" letter-spacing=\"3\">",Str "letter-spacing",Space,Str "set",Space,Str "to",Space,Str "3",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "</g>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "the",Space,Str "space",Space,Str "between",Space,Str "letters",Space,Str "is",Space,Str "different",Space,Str "for",Space,Str "each",Space,Str "line,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-120\" class=\"ctest\">"
,Header 5 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-120"],Space,Code ("",[],[]) "word-spacing"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "word-spacing",Space,Str "attribute",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"100\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\">",Space,RawInline (Format "html") "<g>",Space,RawInline (Format "html") "<text x=\"3\" y=\"20\" word-spacing=\"-3\">",Str "word-spacing",Space,Str "set",Space,Str "to",Space,Str "-3",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text x=\"3\" y=\"50\">",Str "default",Space,Str "word-spacing",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text x=\"3\" y=\"80\" word-spacing=\"8\">",Str "word-spacing",Space,Str "set",Space,Str "to",Space,Str "8",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "</g>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "the",Space,Str "space",Space,Str "between",Space,Str "words",Space,Str "is",Space,Str "different",Space,Str "for",Space,Str "each",Space,Str "line,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-130\" class=\"ctest\">"
,Header 5 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-130"],Space,Code ("",[],[]) "font-size"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "font-size",Space,Str "attribute",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"100\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\">",Space,RawInline (Format "html") "<g>",Space,RawInline (Format "html") "<text x=\"3\" y=\"20\">",Str "default",Space,Str "font-size",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text x=\"3\" y=\"50\" font-size=\"30\">",Str "font-size",Space,Str "set",Space,Str "to",Space,Str "30",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text x=\"3\" y=\"80\" font-size=\"200%\">",Str "The",Space,Str "size",Space,Str "set",Space,Str "to",Space,Str "200%",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "</g>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "the",Space,Str "size",Space,Str "of",Space,Str "the",Space,Str "two",Space,Str "last",Space,Str "lines",Space,Str "is",Space,Str "different",Space,Str "than",Space,Str "the",Space,Str "first",Space,Str "line,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-140\" class=\"ctest\">"
,Header 5 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-140"],Space,Code ("",[],[]) "font-weight"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "font-weight",Space,Str "attribute",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"70\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\">",Space,RawInline (Format "html") "<g>",Space,RawInline (Format "html") "<text x=\"3\" y=\"20\">",Str "default",Space,Str "font-weight",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text x=\"3\" y=\"50\" font-weight=\"bold\">",Str "font-weight",Space,Str "set",Space,Str "to",Space,Str "bold",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "</g>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "the",Space,Str "weight",Space,Str "of",Space,Str "the",Space,Str "second",Space,Str "line",Space,Str "is",Space,Str "different",Space,Str "than",Space,Str "the",Space,Str "first",Space,Str "line,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-150\" class=\"ctest\">"
,Header 5 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-150"],Space,Code ("",[],[]) "font-style"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "font-style",Space,Str "attribute",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"70\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\">",Space,RawInline (Format "html") "<g>",Space,RawInline (Format "html") "<text x=\"3\" y=\"20\">",Str "default",Space,Str "font-style",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text x=\"3\" y=\"50\" font-style=\"italic\">",Str "font-style",Space,Str "set",Space,Str "to",Space,Str "italic",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "</g>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "the",Space,Str "font-style",Space,Str "of",Space,Str "the",Space,Str "second",Space,Str "line",Space,Str "is",Space,Str "different",Space,Str "than",Space,Str "the",Space,Str "first",Space,Str "line,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-160\" class=\"ctest\">"
,Header 5 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-160"],Space,Code ("",[],[]) "text-decoration",Space,Str "attribute"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "text-decoration",Space,Str "attribute",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"100\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\">",Space,RawInline (Format "html") "<g>",Space,RawInline (Format "html") "<text x=\"3\" y=\"20\">",Str "default",Space,Str "text-decoration",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text x=\"3\" y=\"50\" text-decoration=\"underline\">",Str "text-decoration",Space,Str "set",Space,Str "to",Space,Str "underline",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text x=\"3\" y=\"80\" text-decoration=\"line-through\">",Str "text-decoration",Space,Str "set",Space,Str "to",Space,Str "line-through",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "</g>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "the",Space,Str "second",Space,Str "line",Space,Str "is",Space,Str "underlined",Space,Str "and",Space,Str "the",Space,Str "third",Space,Str "has",Space,Str "a",Space,Str "line",Space,Str "through",Space,Str "the",Space,Str "text,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-text-pos\">"
,Header 4 ("",[],[]) [Str "Positioning"]
,RawBlock (Format "html") "<section id=\"svg-210\" class=\"ctest\">"
,Header 5 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-210"],Space,Str "Lines"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "x",Space,Str "and",Space,Code ("",[],[]) "y",Space,Str "attributes",Space,Str "on",Space,Code ("",[],[]) "text",Space,Str "elements",Space,Str "for",Space,Str "positioning",Space,Str "lines",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"250\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\">",Space,RawInline (Format "html") "<text x=\"2\" y=\"20\">",Str "First",Space,Str "text",Space,Str "line",Space,Str "using",Space,Str "SVG",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text x=\"30\" y=\"100\">",Str "Second",Space,Str "text",Space,Str "line",Space,Str "using",Space,Str "SVG",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text x=\"80\" y=\"200\">",Str "Third",Space,Str "and",Space,Str "last",Space,Str "text",Space,Str "line",Space,Str "using",Space,Str "SVG",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "the",Space,Str "vertical",Space,Str "alignment",Space,Str "of",Space,Str "the",Space,Str "three",Space,Str "lines",Space,Str "is",Space,Str "different,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-220\" class=\"ctest\">"
,Header 5 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-220"],Space,Str "Words",Space,Str "and",Space,Str "Characters"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Str "SVG",Space,Str "code",Space,Str "for",Space,Str "positioning",Space,Str "words",Space,Str "or",Space,Str "characters",Space,Str "is",Space,Str "supported",Space,Str "using",Space,Str "the",Space,Code ("",[],[]) "text",Space,Str "and",Space,Code ("",[],[]) "tspan",Space,Str "elements."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"100\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\">",Space,RawInline (Format "html") "<text x=\"100\" y=\"80\">",Str "This",Space,RawInline (Format "html") "<tspan dy=\"-2\">",Str "i",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"-3\">",Str "s",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"-4\">",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"-5\">",Str "a",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"-6\">",Space,RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"-8\">",Str "v",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"-9\">",Str "e",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"-8\">",Str "e",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"-7\">",Str "e",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<!-- -59 -->",Space,RawInline (Format "html") "<tspan dy=\"9\">",Str "r",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"10\">",Str "y",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"9\">",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"8\">",Str "b",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"7\">",Str "i",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"6\">",Str "i",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"5\">",Str "i",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"3\">",Str "g",RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<tspan dy=\"2\">",Space,RawInline (Format "html") "</tspan>",Space,RawInline (Format "html") "<!-- +59 -->",Space,Str "wave.",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "the",Space,Str "text",Space,Str "\"This",Space,Str "is",Space,Str "a",Space,Str "veeery",Space,Str "biiig",Space,Str "wave\"",Space,Str "rises",Space,Str "and",Space,Str "falls",Space,Str "in",Space,Str "an",Space,Str "arc",Space,Str "like",Space,Str "a",Space,Str "wave,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-230\" class=\"ctest\">"
,Header 5 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-230"],Space,Str "Text:",Space,Code ("",[],[]) "path",Space,Str "element"]
,Para [Str "Tests",Space,Str "whether",Space,Str "positioning",Space,Str "text",Space,Str "on",Space,Str "a",Space,Str "path",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"120\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\" xlink=\"http://www.w3.org/1999/xlink\">",Space,RawInline (Format "html") "<g>",Space,RawInline (Format "html") "<defs>",Space,RawInline (Format "html") "<path id=\"Path1\" fill=\"none\" stroke=\"black\" d=\"M199 89.3 C206.6 66.6 235.8 13.2 270 30.3 286.6 38.6 298.9 59.4 310 73.3 321.7 87.9 338.6 99 356 103.3 387.3 111.1 396.6 90.4 418 74.3\">",RawInline (Format "html") "</path>",Space,RawInline (Format "html") "</defs>",Space,RawInline (Format "html") "<g id=\"text-on-path-01\">",Space,RawInline (Format "html") "<use href=\"#Path1\">",RawInline (Format "html") "</use>",Space,RawInline (Format "html") "<text>",Space,RawInline (Format "html") "<textpath href=\"#Path1\">",Str "The",Space,Str "text",Space,Str "follows",Space,Str "its",Space,Str "own",Space,Str "path.",Space,Str "Can",Space,Str "you",Space,Str "see",Space,Str "it?",RawInline (Format "html") "</textpath>",Space,RawInline (Format "html") "</text>",Space,RawInline (Format "html") "</g>",Space,RawInline (Format "html") "</g>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "the",Space,Str "text",Space,Str "follows",Space,Str "a",Space,Str "parabolic",Space,Str "path,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-240\" class=\"ctest\">"
,Header 5 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-240"],Space,Str "Text:",Space,Code ("",[],[]) "text",Space,Str "element",Space,Str "with",Space,Str "multiple",Space,Code ("",[],[]) "x",Space,Str "and",Space,Code ("",[],[]) "y",Space,Str "values"]
,Para [Str "Tests",Space,Str "whether",Space,Str "multiple",Space,Str "values",Space,Str "of",Space,Str "the",Space,Code ("",[],[]) "x",Space,Str "and",Space,Code ("",[],[]) "y",Space,Str "attributes",Space,Str "are",Space,Str "supported."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"250\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\" xlink=\"http://www.w3.org/1999/xlink\">",Space,RawInline (Format "html") "<g>",Space,RawInline (Format "html") "<text x=\"160 180 200 220 240 260 280 300 320 340 360\" y=\"30 50 70 90 110 130 150 170 190 210 230\">",Str "Multiple",Space,Str "x",Space,Str "y",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "</g>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "the",Space,Str "text",Space,Str "goes",Space,Str "down,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-text-rotate\">"
,Header 4 ("",[],[]) [Str "Rotating"]
,RawBlock (Format "html") "<section id=\"svg-310\" class=\"ctest\">"
,Header 5 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-310"],Space,Code ("",[],[]) "rotate"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "rotate",Space,Str "attribute",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"100\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\" xlink=\"http://www.w3.org/1999/xlink\">",Space,RawInline (Format "html") "<g>",Space,RawInline (Format "html") "<text x=\"10\" y=\"50\" rotate=\"0 10 40\">",Str "This",Space,Str "text",Space,Str "is",Space,Str "rotated",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "</g>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "the",Space,Str "characters",Space,Str "in",Space,Str "the",Space,Str "preceding",Space,Str "sentence",Space,Str "are",Space,Str "rotated,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-320\" class=\"ctest\">"
,Header 5 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-320"],Space,Code ("",[],[]) "transform"]
,Para [Str "Tests",Space,Str "whether",Space,Code ("",[],[]) "transform",Space,Str "attribute",Space,Str "(translate",Space,Str "and",Space,Str "rotate",Space,Str "values)",Space,Str "are",Space,Str "supported."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"250\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\" xlink=\"http://www.w3.org/1999/xlink\">",Space,RawInline (Format "html") "<g>",Space,RawInline (Format "html") "<text transform=\"rotate(90) translate(120 -100)\">",Str "90",Space,Str "degrees",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text transform=\"rotate(-90) translate(-120 100)\">",Str "-90",Space,Str "degrees",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "<text transform=\"rotate(180) translate(-120 -200)\">",Str "180",Space,Str "degrees",RawInline (Format "html") "</text>",Space,RawInline (Format "html") "</g>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "each",Space,Str "line",Space,Str "of",Space,Str "text",Space,Str "is",Space,Str "rotated",Space,Str "by",Space,Str "the",Space,Str "degree",Space,Str "it",Space,Str "indicates,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,Para [Span ("content-svg-003.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section id=\"svg-xhtml-support\">"
,Header 3 ("",[],[]) [Str "XHTML",Space,Str "Support"]
,RawBlock (Format "html") "<section id=\"svg-410\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-410"],Space,Code ("",[],[]) "img"]
,Para [Str "Tests",Space,Str "whether",Space,Str "SVG",Space,Str "is",Space,Str "supported",Space,Str "in",Space,Code ("",[],[]) "img",Space,Str "elements."]
,Para [Image [Str "a",Space,Str "grey",Space,Str "circle"] ("circle.svg","")]
,Para [Str "If",Space,Str "a",Space,Str "grey",Space,Str "circle",Space,Str "is",Space,Str "rendered",Space,Str "before",Space,Str "this",Space,Str "paragraph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-420\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-420"],Space,Code ("",[],[]) "object"]
,Para [Str "Tests",Space,Str "whether",Space,Str "SVG",Space,Str "is",Space,Str "supported",Space,Str "in",Space,Code ("",[],[]) "object",Space,Str "elements."]
,Para [RawInline (Format "html") "<object type=\"image/svg+xml\" data=\"../svg/circle.svg\">"]
,Para [Str "FAIL"]
,Para [RawInline (Format "html") "</object>"]
,Para [Str "If",Space,Str "a",Space,Str "circle",Space,Str "is",Space,Str "rendered",Space,Str "before",Space,Str "this",Space,Str "paragraph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"svg-430\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-430"],Space,Code ("",[],[]) "background-image",Space,Str "(CSS)"]
,Para [Str "Tests",Space,Str "whether",Space,Str "SVG",Space,Str "is",Space,Str "supported",Space,Str "when",Space,Str "set",Space,Str "using",Space,Str "the",Space,Str "CSS",Space,Code ("",[],[]) "background-image",Space,Str "property."]
,Para [Str "If",Space,Str "a",Space,Str "grey",Space,Str "circle",Space,Str "is",Space,Str "rendered",Space,Str "at",Space,Str "the",Space,Str "right",Space,Str "bottom",Space,Str "of",Space,Str "this",Space,Str "section,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,Para [Span ("content-svg-004.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section id=\"svg-image-embed\">"
,Header 3 ("",[],[]) [Str "Image",Space,Str "Embedding"]
,RawBlock (Format "html") "<section id=\"svg-510\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "svg-510"],Space,Str "Bitmaps"]
,Para [Str "Tests",Space,Str "whether",Space,Str "bitmap",Space,Str "images",Space,Str "can",Space,Str "be",Space,Str "embedded",Space,Str "in",Space,Str "an",Space,Str "SVG",Space,Str "image."]
,Para [RawInline (Format "html") "<svg width=\"100%\" height=\"200\" version=\"1.1\" xmlns=\"http://www.w3.org/2000/svg\" xlink=\"http://www.w3.org/1999/xlink\">",Space,RawInline (Format "html") "<image x=\"20\" y=\"20\" width=\"182px\" height=\"185px\" href=\"../img/circle.jpg\">",RawInline (Format "html") "</image>",Space,RawInline (Format "html") "</svg>"]
,Para [Str "If",Space,Str "a",Space,Str "black",Space,Str "circle",Space,Str "is",Space,Str "rendered",Space,Str "before",Space,Str "this",Space,Str "paragraph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,Para [Span ("content-fallbacks.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"utf-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,Header 1 ("",[],[]) [Str "Fallbacks"]
,Para [Str "This",Space,Str "section",Space,Str "contains",Space,Str "tests",Space,Str "for",Space,Str "Fallbacks."]
,Para [Span ("content-bindings-001.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"utf-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section id=\"bindings\">"
,Header 3 ("",[],[]) [Str "Bindings"]
,RawBlock (Format "html") "<section id=\"bindings-010\" class=\"otest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "bindings-010"],Space,Code ("",[],[]) "bindings"]
,Para [Str "Tests",Space,Str "whether",Space,Str "bindings",Space,Str "on",Space,Code ("",[],[]) "object",Str "s",Space,Str "are",Space,Str "supported."]
,Para [RawInline (Format "html") "<object data=\"../bindings/slideshow.xml\" type=\"application/x-demo-slideshow\">",Space,RawInline (Format "html") "<param name=\"success\" value=\"PASS\">",RawInline (Format "html") "</param>"]
,Para [Str "FAIL"]
,Para [Str "The",Space,Str "slideshow",Space,Str "binding",Space,Str "was",Space,Str "not",Space,Str "called"]
,Para [RawInline (Format "html") "</object>"]
,Para [Str "If",Space,Str "the",Space,Str "preceding",Space,Str "paragraph",Space,Str "reads",Space,Str "\"PASS\",",Space,Str "the",Space,Str "test",Space,Str "passes.",Space,Str "Other",Space,Str "messages",Space,Str "may",Space,Str "indicate",Space,Str "partial",Space,Str "support."]
,Para [Str "If",Space,Str "the",Space,Str "reading",Space,Str "system",Space,Str "does",Space,Str "not",Space,Str "support",Space,Str "scripting,",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 ("content-fallbacks-001.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section id=\"fallbacks\">"
,Header 2 ("",[],[]) [Str "Fallbacks"]
,RawBlock (Format "html") "<section id=\"fallbacks-manifest\">"
,Header 3 ("",[],[]) [Str "Manifest"]
,RawBlock (Format "html") "<section id=\"fallback-010\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "fallback-010"],Space,Str "Image",Space,Str "fallbacks"]
,Para [Str "Tests",Space,Str "whether",Space,Str "manifest",Space,Str "fallbacks",Space,Str "for",Space,Str "non-core",Space,Str "image",Space,Str "media",Space,Str "types",Space,Str "are",Space,Str "supported."]
,Para [Image [Str "test"] ("nonimage.xyz","")]
,Para [Str "If",Space,Str "an",Space,Str "image",Space,Str "of",Space,Str "a",Space,Str "checkmark",Space,Str "is",Space,Str "rendered",Space,Str "before",Space,Str "this",Space,Str "paragraph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"fallback-020\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "fallback-020"],Space,Str "Inline",Space,Str "frame",Space,Str "fallbacks"]
,Para [Str "Tests",Space,Str "whether",Space,Str "manifest",Space,Str "fallbacks",Space,Str "for",Space,Str "non-core",Space,Str "media",Space,Str "types",Space,Str "used",Space,Str "in",Space,Code ("",[],[]) "iframe",Str "s",Space,Str "are",Space,Str "supported."]
,Para [RawInline (Format "html") "<iframe src=\"../img/nonimage.xyz\">",RawInline (Format "html") "</iframe>"]
,Para [Str "If",Space,Str "an",Space,Str "image",Space,Str "of",Space,Str "a",Space,Str "checkmark",Space,Str "is",Space,Str "rendered",Space,Str "before",Space,Str "this",Space,Str "paragraph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"fallback-030\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "fallback-030"],Space,Str "Embed",Space,Str "fallbacks"]
,Para [Str "Tests",Space,Str "whether",Space,Str "manifest",Space,Str "fallbacks",Space,Str "for",Space,Str "non-core",Space,Str "media",Space,Str "types",Space,Str "used",Space,Str "in",Space,Code ("",[],[]) "embed",Str "s",Space,Str "are",Space,Str "supported."]
,RawBlock (Format "html") "<embed src=\"../img/nonimage.xyz\" type=\"image/xyz\">"
,RawBlock (Format "html") "</embed>"
,Para [Str "If",Space,Str "an",Space,Str "image",Space,Str "of",Space,Str "a",Space,Str "checkmark",Space,Str "is",Space,Str "rendered",Space,Str "before",Space,Str "this",Space,Str "paragraph,",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"fallbacks-intrinsic\">"
,Header 3 ("",[],[]) [Str "Intrinsic"]
,RawBlock (Format "html") "<section id=\"fallback-040\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "fallback-040"],Space,Str "Object",Space,Str "fallbacks"]
,Para [Str "Tests",Space,Str "whether",Space,Code ("",[],[]) "object",Str "'s",Space,Str "intrinsic",Space,Str "fallback",Space,Str "mechanism",Space,Str "for",Space,Str "non-core",Space,Str "media",Space,Str "types",Space,Str "is",Space,Str "supported."]
,Para [RawInline (Format "html") "<object data=\"../img/nonimage.xyz\" type=\"image/xyz\">",Space,RawInline (Format "html") "<object data=\"../img/nonimage.xyz\" type=\"image/xyz\">"]
,Para [Str "PASS"]
,Para [RawInline (Format "html") "</object>",Space,RawInline (Format "html") "</object>"]
,Para [Str "If",Space,Str "the",Space,Str "preceding",Space,Str "paragraph",Space,Str "reads",Space,Str "\"PASS\",",Space,Str "the",Space,Str "test",Space,Str "passes."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "</section>"
,Para [Span ("content-switch-001.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"UTF-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,RawBlock (Format "html") "<section id=\"epub-switch\">"
,Header 3 ("",[],[]) [Code ("",[],[]) "epub:switch"]
,RawBlock (Format "html") "<section id=\"switch-010\" class=\"ctest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "switch-010"],Space,Str "Support"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "epub:switch",Space,Str "element",Space,Str "is",Space,Str "supported."]
,Para [Str "PASS"]
,Para [Str "If",Space,Str "only",Space,Str "the",Space,Str "word",Space,Str "\"PASS\"",Space,Str "is",Space,Str "rendered",Space,Str "before",Space,Str "this",Space,Str "paragraph,",Space,Str "the",Space,Str "test",Space,Str "passes.",Space,Str "If",Space,Str "both",Space,Str "\"PASS\"",Space,Str "and",Space,Str "\"FAIL\"",Space,Str "are",Space,Str "rendered,",Space,Str "or",Space,Str "neither",Space,Str "\"PASS\"",Space,Str "nor",Space,Str "\"FAIL\"",Space,Str "is",Space,Str "rendered,",Space,Str "the",Space,Str "test",Space,Str "fails."]
,RawBlock (Format "html") "</section>"
,RawBlock (Format "html") "<section id=\"switch-020\" class=\"otest\">"
,Header 4 ("",[],[]) [Span ("",["nature"],[]) [Str "[OPTIONAL]"],Space,Span ("",["test-id"],[]) [Str "switch-020"],Space,Str "MathML",Space,Str "Embedding"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Str "MathML",Space,Str "namespace",Space,Str "is",Space,Str "recognized",Space,Str "when",Space,Str "used",Space,Str "in",Space,Str "an",Space,Code ("",[],[]) "epub:case",Space,Str "element."]
,Para [Math InlineMath "{2x}{+y-z}"]
,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 ("svg-doc-001.xhtml",[],[]) []]
,Para [RawInline (Format "html") "<?xml version=\"1.0\" encoding=\"utf-8\" ?>",Space,RawInline (Format "html") "<!DOCTYPE html>"]
,Header 1 ("",[],[]) [Str "Content",Space,Str "Documents:",Space,Str "SVG"]
,Para [Str "This",Space,Str "section",Space,Str "contains",Space,Str "tests",Space,Str "for",Space,Str "static",Space,Str "SVG",Space,Str "content."]
,Para [Str "Note",Space,Str "that",Space,Str "if",Space,Str "no",Space,Str "SVG",Space,Str "tests",Space,Str "appear",Space,Str "after",Space,Str "this",Space,Str "document,",Space,Str "SVG",Space,Str "is",Space,Str "not",Space,Str "supported",Space,Str "in",Space,Str "the",Space,Str "spine",Space,Str "and",Space,Str "all",Space,Str "tests",Space,Str "in",Space,Str "this",Space,Str "section",Space,Str "should",Space,Str "be",Space,Str "marked",Space,Code ("",[],[]) "Not Supported",Str "."]
,Para [Span ("content-svg-001.svg",[],[]) []]]

BIN
tests/formatting.epub Normal file

Binary file not shown.

454
tests/formatting.native Normal file

File diff suppressed because one or more lines are too long