Merge branch 'new-image-attributes' of https://github.com/mb21/pandoc into mb21-new-image-attributes

* Bumped version to 1.16.
* Added Attr field to Link and Image.
* Added `common_link_attributes` extension.
* Updated readers for link attributes.
* Updated writers for link attributes.
* Updated tests
* Updated stack.yaml to build against unreleased versions of
  pandoc-types and texmath.
* Fixed various compiler warnings.

Closes #261.

TODO:

* Relative (percentage) image widths in docx writer.
* ODT/OpenDocument writer (untested, same issue about percentage widths).
* Update pandoc-citeproc.
This commit is contained in:
John MacFarlane 2015-11-19 22:41:12 -08:00
commit 244cd5644b
81 changed files with 1181 additions and 748 deletions

67
README
View file

@ -517,14 +517,22 @@ General writer options
: Print a system default data file. Files in the user data directory : Print a system default data file. Files in the user data directory
are ignored. are ignored.
`--dpi`=*NUMBER*
: Specify the dpi (dots per inch) value for conversion from pixels
to inch/centimeters and vice versa. The default is 96dpi.
Technically, the correct term would be ppi (pixels per inch).
`--no-wrap` `--no-wrap`
: Disable text wrapping in output. By default, text is wrapped : Disable text wrapping in output. By default, text is wrapped
appropriately for the output format. appropriately for the output format. This affects only the
generated source code, not the layout on the rendered page.
`--columns=`*NUMBER* `--columns=`*NUMBER*
: Specify length of lines in characters (for text wrapping). : Specify length of lines in characters (for text wrapping).
This affects only the generated source code, not the layout on
the rendered page.
`--toc`, `--table-of-contents` `--toc`, `--table-of-contents`
@ -2909,6 +2917,49 @@ nonbreaking space after the image:
![This image won't be a figure](/url/of/image.png)\ ![This image won't be a figure](/url/of/image.png)\
#### Extension: `common_link_attributes` ####
Attributes can be set on links and images:
An inline ![image](foo.jpg){#id .class width=30 height=20px}
and a reference ![image][ref] with attributes.
[ref]: foo.jpg "optional title" {#id .class key=val key2="val 2"}
(This syntax is compatible with [PHP Markdown Extra] when only `#id`
and `.class` are used.)
For HTML and EPUB, all attributes except `width` and `height` (but
including `srcset` and `sizes`) are passed through as is. The other
writers ignore attributes that are not supported by their output
format.
The `width` and `height` attributes on images are treated specially. When
used without a unit, the unit is assumed to be pixels. However, any of
the following unit identifiers can be used: `px`, `cm`, `mm`, `in`, `inch`
and `%`. There must not be any spaces between the number and the unit.
For example:
```
![](file.jpg){ width=50% }
```
- Dimensions are converted to inches for output in page-based formats like
LaTeX. Dimensions are converted to pixels for output in HTML-like
formats. Use the `--dpi` option to specify the number of pixels per
inch. The default is 96dpi.
- The `%` unit is generally relative to some available space.
For example the above example will render to
`<img href="file.jpg" style="width: 50%;" />` (HTML),
`\includegraphics[width=0.5\textwidth]{file.jpg}` (LaTeX), or
`\externalfigure[file.jpg][width=0.5\textwidth]` (ConTeXt).
- Some output formats have a notion of a class
([ConTeXt](http://wiki.contextgarden.net/Using_Graphics#Multiple_Image_Settings))
or a unique identifier (LaTeX `\caption`), or both (HTML).
- When no `width` or `height` attributes are specified, the fallback
is to look at the image resolution and the dpi metadata embedded in
the image file.
Footnotes Footnotes
--------- ---------
@ -3221,9 +3272,14 @@ letters are omitted.
#### Extension: `link_attributes` #### #### Extension: `link_attributes` ####
Parses multimarkdown style key-value attributes on link and image references. Parses multimarkdown style key-value attributes on link
Note that pandoc's internal document model provides nowhere to put and image references. This extension should not be confused with the
these, so they are presently just ignored. [`common_link_attributes`](#extension-common_link_attributes) extension.
This is a reference ![image][ref] with multimarkdown attributes.
[ref]: http://path.to/image "Image title" width=20px height=30px
id=myId class="myClass1 myClass2"
#### Extension: `mmd_header_identifiers` #### #### Extension: `mmd_header_identifiers` ####
@ -3266,7 +3322,8 @@ variants are supported:
`markdown_phpextra` (PHP Markdown Extra) `markdown_phpextra` (PHP Markdown Extra)
: `footnotes`, `pipe_tables`, `raw_html`, `markdown_attribute`, : `footnotes`, `pipe_tables`, `raw_html`, `markdown_attribute`,
`fenced_code_blocks`, `definition_lists`, `intraword_underscores`, `fenced_code_blocks`, `definition_lists`, `intraword_underscores`,
`header_attributes`, `abbreviations`, `shortcut_reference_links`. `header_attributes`, `common_link_attributes`, `abbreviations`,
`shortcut_reference_links`.
`markdown_github` (GitHub-Flavored Markdown) `markdown_github` (GitHub-Flavored Markdown)
: `pipe_tables`, `raw_html`, `tex_math_single_backslash`, : `pipe_tables`, `raw_html`, `tex_math_single_backslash`,

View file

@ -1,5 +1,5 @@
Name: pandoc Name: pandoc
Version: 1.15.2.1 Version: 1.16
Cabal-Version: >= 1.10 Cabal-Version: >= 1.10
Build-Type: Custom Build-Type: Custom
License: GPL License: GPL
@ -264,7 +264,7 @@ Library
xml >= 1.3.12 && < 1.4, xml >= 1.3.12 && < 1.4,
random >= 1 && < 1.2, random >= 1 && < 1.2,
extensible-exceptions >= 0.1 && < 0.2, extensible-exceptions >= 0.1 && < 0.2,
pandoc-types >= 1.12.4 && < 1.13, pandoc-types >= 1.16 && < 1.17,
aeson >= 0.7 && < 0.11, aeson >= 0.7 && < 0.11,
tagsoup >= 0.13.1 && < 0.14, tagsoup >= 0.13.1 && < 0.14,
base64-bytestring >= 0.1 && < 1.1, base64-bytestring >= 0.1 && < 1.1,
@ -412,7 +412,7 @@ Library
Executable pandoc Executable pandoc
Build-Depends: pandoc, Build-Depends: pandoc,
pandoc-types >= 1.12.4 && < 1.13, pandoc-types >= 1.16 && < 1.17,
base >= 4.2 && <5, base >= 4.2 && <5,
directory >= 1 && < 1.3, directory >= 1 && < 1.3,
filepath >= 1.1 && < 1.5, filepath >= 1.1 && < 1.5,
@ -469,7 +469,7 @@ Test-Suite test-pandoc
Build-Depends: base >= 4.2 && < 5, Build-Depends: base >= 4.2 && < 5,
syb >= 0.1 && < 0.7, syb >= 0.1 && < 0.7,
pandoc, pandoc,
pandoc-types >= 1.12.4 && < 1.13, pandoc-types >= 1.16 && < 1.17,
bytestring >= 0.9 && < 0.11, bytestring >= 0.9 && < 0.11,
text >= 0.11 && < 1.3, text >= 0.11 && < 1.3,
directory >= 1 && < 1.3, directory >= 1 && < 1.3,

View file

@ -196,6 +196,7 @@ data Opt = Opt
, optIgnoreArgs :: Bool -- ^ Ignore command-line arguments , optIgnoreArgs :: Bool -- ^ Ignore command-line arguments
, optVerbose :: Bool -- ^ Verbose diagnostic output , optVerbose :: Bool -- ^ Verbose diagnostic output
, optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst , optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
, optDpi :: Int -- ^ Dpi
, optWrapText :: Bool -- ^ Wrap text , optWrapText :: Bool -- ^ Wrap text
, optColumns :: Int -- ^ Line length in characters , optColumns :: Int -- ^ Line length in characters
, optFilters :: [FilePath] -- ^ Filters to apply , optFilters :: [FilePath] -- ^ Filters to apply
@ -258,6 +259,7 @@ defaultOpts = Opt
, optIgnoreArgs = False , optIgnoreArgs = False
, optVerbose = False , optVerbose = False
, optReferenceLinks = False , optReferenceLinks = False
, optDpi = 96
, optWrapText = True , optWrapText = True
, optColumns = 72 , optColumns = 72
, optFilters = [] , optFilters = []
@ -454,6 +456,16 @@ options =
"FILE") "FILE")
"" -- "Print default data file" "" -- "Print default data file"
, Option "" ["dpi"]
(ReqArg
(\arg opt ->
case safeRead arg of
Just t | t > 0 -> return opt { optDpi = t }
_ -> err 31
"dpi must be a number greater than 0")
"NUMBER")
"" -- "Dpi (default 96)"
, Option "" ["no-wrap"] , Option "" ["no-wrap"]
(NoArg (NoArg
(\opt -> return opt { optWrapText = False })) (\opt -> return opt { optWrapText = False }))
@ -1029,8 +1041,8 @@ extractMedia media dir d =
return $ walk (adjustImagePath dir fps) d return $ walk (adjustImagePath dir fps) d
adjustImagePath :: FilePath -> [FilePath] -> Inline -> Inline adjustImagePath :: FilePath -> [FilePath] -> Inline -> Inline
adjustImagePath dir paths (Image lab (src, tit)) adjustImagePath dir paths (Image attr lab (src, tit))
| src `elem` paths = Image lab (dir ++ "/" ++ src, tit) | src `elem` paths = Image attr lab (dir ++ "/" ++ src, tit)
adjustImagePath _ _ x = x adjustImagePath _ _ x = x
adjustMetadata :: M.Map String MetaValue -> Pandoc -> IO Pandoc adjustMetadata :: M.Map String MetaValue -> Pandoc -> IO Pandoc
@ -1104,6 +1116,7 @@ main = do
, optIgnoreArgs = ignoreArgs , optIgnoreArgs = ignoreArgs
, optVerbose = verbose , optVerbose = verbose
, optReferenceLinks = referenceLinks , optReferenceLinks = referenceLinks
, optDpi = dpi
, optWrapText = wrap , optWrapText = wrap
, optColumns = columns , optColumns = columns
, optFilters = filters , optFilters = filters
@ -1327,6 +1340,7 @@ main = do
writerNumberOffset = numberFrom, writerNumberOffset = numberFrom,
writerSectionDivs = sectionDivs, writerSectionDivs = sectionDivs,
writerReferenceLinks = referenceLinks, writerReferenceLinks = referenceLinks,
writerDpi = dpi,
writerWrapText = wrap, writerWrapText = wrap,
writerColumns = columns, writerColumns = columns,
writerEmailObfuscation = obfuscationMethod, writerEmailObfuscation = obfuscationMethod,

View file

@ -266,7 +266,7 @@ writers = [
,("html" , PureStringWriter writeHtmlString) ,("html" , PureStringWriter writeHtmlString)
,("html5" , PureStringWriter $ \o -> ,("html5" , PureStringWriter $ \o ->
writeHtmlString o{ writerHtml5 = True }) writeHtmlString o{ writerHtml5 = True })
,("icml" , PureStringWriter writeICML) ,("icml" , IOStringWriter writeICML)
,("s5" , PureStringWriter $ \o -> ,("s5" , PureStringWriter $ \o ->
writeHtmlString o{ writerSlideVariant = S5Slides writeHtmlString o{ writerSlideVariant = S5Slides
, writerTableOfContents = False }) , writerTableOfContents = False })

View file

@ -29,16 +29,36 @@ Portability : portable
Functions for determining the size of a PNG, JPEG, or GIF image. Functions for determining the size of a PNG, JPEG, or GIF image.
-} -}
module Text.Pandoc.ImageSize ( ImageType(..), imageType, imageSize, module Text.Pandoc.ImageSize ( ImageType(..)
sizeInPixels, sizeInPoints ) where , imageType
, imageSize
, sizeInPixels
, sizeInPoints
, desiredSizeInPoints
, Dimension(..)
, Direction(..)
, dimension
, inInch
, inPoints
, numUnit
, showInInch
, showInPixel
, showFl
) where
import Data.ByteString (ByteString, unpack) import Data.ByteString (ByteString, unpack)
import qualified Data.ByteString.Char8 as B import qualified Data.ByteString.Char8 as B
import qualified Data.ByteString.Lazy as BL import qualified Data.ByteString.Lazy as BL
import Data.Char (isDigit)
import Control.Monad import Control.Monad
import Data.Bits import Data.Bits
import Data.Binary import Data.Binary
import Data.Binary.Get import Data.Binary.Get
import Text.Pandoc.Shared (safeRead, hush) import Text.Pandoc.Shared (safeRead, hush)
import Data.Default (Default)
import Numeric (showFFloat)
import Text.Read (readMaybe)
import Text.Pandoc.Definition
import Text.Pandoc.Options
import qualified Data.Map as M import qualified Data.Map as M
import Text.Pandoc.Compat.Except import Text.Pandoc.Compat.Except
import Control.Monad.Trans import Control.Monad.Trans
@ -48,6 +68,20 @@ import Data.Maybe (fromMaybe)
-- algorithms borrowed from wwwis.pl -- algorithms borrowed from wwwis.pl
data ImageType = Png | Gif | Jpeg | Pdf | Eps deriving Show data ImageType = Png | Gif | Jpeg | Pdf | Eps deriving Show
data Direction = Width | Height
instance Show Direction where
show Width = "width"
show Height = "height"
data Dimension = Pixel Integer
| Centimeter Double
| Inch Double
| Percent Double
instance Show Dimension where
show (Pixel a) = show a ++ "px"
show (Centimeter a) = showFl a ++ "cm"
show (Inch a) = showFl a ++ "in"
show (Percent a) = show a ++ "%"
data ImageSize = ImageSize{ data ImageSize = ImageSize{
pxX :: Integer pxX :: Integer
@ -55,7 +89,11 @@ data ImageSize = ImageSize{
, dpiX :: Integer , dpiX :: Integer
, dpiY :: Integer , dpiY :: Integer
} deriving (Read, Show, Eq) } deriving (Read, Show, Eq)
instance Default ImageSize where
def = ImageSize 300 200 72 72
showFl :: (RealFloat a) => a -> String
showFl a = showFFloat (Just 5) a ""
imageType :: ByteString -> Maybe ImageType imageType :: ByteString -> Maybe ImageType
imageType img = case B.take 4 img of imageType img = case B.take 4 img of
@ -87,8 +125,93 @@ defaultSize = (72, 72)
sizeInPixels :: ImageSize -> (Integer, Integer) sizeInPixels :: ImageSize -> (Integer, Integer)
sizeInPixels s = (pxX s, pxY s) sizeInPixels s = (pxX s, pxY s)
sizeInPoints :: ImageSize -> (Integer, Integer) -- | Calculate (height, width) in points using the image file's dpi metadata,
sizeInPoints s = (pxX s * 72 `div` dpiX s, pxY s * 72 `div` dpiY s) -- using 72 Points == 1 Inch.
sizeInPoints :: ImageSize -> (Double, Double)
sizeInPoints s = (pxXf * 72 / dpiXf, pxYf * 72 / dpiYf)
where
pxXf = fromIntegral $ pxX s
pxYf = fromIntegral $ pxY s
dpiXf = fromIntegral $ dpiX s
dpiYf = fromIntegral $ dpiY s
-- | Calculate (height, width) in points, considering the desired dimensions in the
-- attribute, while falling back on the image file's dpi metadata if no dimensions
-- are specified in the attribute (or only dimensions in percentages).
desiredSizeInPoints :: WriterOptions -> Attr -> ImageSize -> (Double, Double)
desiredSizeInPoints opts attr s =
case (getDim Width, getDim Height) of
(Just w, Just h) -> (w, h)
(Just w, Nothing) -> (w, w / ratio)
(Nothing, Just h) -> (h * ratio, h)
(Nothing, Nothing) -> sizeInPoints s
where
ratio = fromIntegral (pxX s) / fromIntegral (pxY s)
getDim dir = case (dimension dir attr) of
Just (Percent _) -> Nothing
Just dim -> Just $ inPoints opts dim
Nothing -> Nothing
inPoints :: WriterOptions -> Dimension -> Double
inPoints opts dim = 72 * inInch opts dim
inInch :: WriterOptions -> Dimension -> Double
inInch opts dim =
case dim of
(Pixel a) -> fromIntegral a / (fromIntegral $ writerDpi opts)
(Centimeter a) -> a * 0.3937007874
(Inch a) -> a
(Percent _) -> 0
-- | Convert a Dimension to a String denoting its equivalent in inches, for example "2.00000".
-- Note: Dimensions in percentages are converted to the empty string.
showInInch :: WriterOptions -> Dimension -> String
showInInch _ (Percent _) = ""
showInInch opts dim = showFl $ inInch opts dim
-- | Convert a Dimension to a String denoting its equivalent in pixels, for example "600".
-- Note: Dimensions in percentages are converted to the empty string.
showInPixel :: WriterOptions -> Dimension -> String
showInPixel opts dim =
case dim of
(Pixel a) -> show a
(Centimeter a) -> show (floor $ dpi * a * 0.3937007874 :: Int)
(Inch a) -> show (floor $ dpi * a :: Int)
(Percent _) -> ""
where
dpi = fromIntegral $ writerDpi opts
-- | Maybe split a string into a leading number and trailing unit, e.g. "3cm" to Just (3.0, "cm")
numUnit :: String -> Maybe (Double, String)
numUnit s =
let (nums, unit) = span (\c -> isDigit c || ('.'==c)) s
in case readMaybe nums of
Just n -> Just (n, unit)
Nothing -> Nothing
-- | Read a Dimension from an Attr attribute.
-- `dimension Width attr` might return `Just (Pixel 3)` or for example `Just (Centimeter 2.0)`, etc.
dimension :: Direction -> Attr -> Maybe Dimension
dimension dir (_, _, kvs) =
case dir of
Width -> extractDim "width"
Height -> extractDim "height"
where
extractDim key =
case lookup key kvs of
Just str ->
case numUnit str of
Just (num, unit) -> toDim num unit
Nothing -> Nothing
Nothing -> Nothing
toDim a "cm" = Just $ Centimeter a
toDim a "mm" = Just $ Centimeter (a / 10)
toDim a "in" = Just $ Inch a
toDim a "inch" = Just $ Inch a
toDim a "%" = Just $ Percent a
toDim a "px" = Just $ Pixel (floor a::Integer)
toDim a "" = Just $ Pixel (floor a::Integer)
toDim _ _ = Nothing
epsSize :: ByteString -> Maybe ImageSize epsSize :: ByteString -> Maybe ImageSize
epsSize img = do epsSize img = do
@ -278,15 +401,15 @@ exifHeader hdr = do
return (tag, payload) return (tag, payload)
entries <- sequence $ replicate (fromIntegral numentries) ifdEntry entries <- sequence $ replicate (fromIntegral numentries) ifdEntry
subentries <- case lookup ExifOffset entries of subentries <- case lookup ExifOffset entries of
Just (UnsignedLong offset) -> do Just (UnsignedLong offset') -> do
pos <- lift bytesRead pos <- lift bytesRead
lift $ skip (fromIntegral offset - (fromIntegral pos - 8)) lift $ skip (fromIntegral offset' - (fromIntegral pos - 8))
numsubentries <- lift getWord16 numsubentries <- lift getWord16
sequence $ sequence $
replicate (fromIntegral numsubentries) ifdEntry replicate (fromIntegral numsubentries) ifdEntry
_ -> return [] _ -> return []
let allentries = entries ++ subentries let allentries = entries ++ subentries
(width, height) <- case (lookup ExifImageWidth allentries, (wdth, hght) <- case (lookup ExifImageWidth allentries,
lookup ExifImageHeight allentries) of lookup ExifImageHeight allentries) of
(Just (UnsignedLong w), Just (UnsignedLong h)) -> (Just (UnsignedLong w), Just (UnsignedLong h)) ->
return (fromIntegral w, fromIntegral h) return (fromIntegral w, fromIntegral h)
@ -301,8 +424,8 @@ exifHeader hdr = do
let yres = maybe 72 (\(UnsignedRational x) -> floor $ x * resfactor) let yres = maybe 72 (\(UnsignedRational x) -> floor $ x * resfactor)
$ lookup YResolution allentries $ lookup YResolution allentries
return $ ImageSize{ return $ ImageSize{
pxX = width pxX = wdth
, pxY = height , pxY = hght
, dpiX = xres , dpiX = xres
, dpiY = yres } , dpiY = yres }

View file

@ -86,6 +86,7 @@ data Extension =
| Ext_markdown_attribute -- ^ Interpret text inside HTML as markdown | Ext_markdown_attribute -- ^ Interpret text inside HTML as markdown
-- iff container has attribute 'markdown' -- iff container has attribute 'markdown'
| Ext_escaped_line_breaks -- ^ Treat a backslash at EOL as linebreak | Ext_escaped_line_breaks -- ^ Treat a backslash at EOL as linebreak
| Ext_common_link_attributes -- ^ link and image attributes
| Ext_link_attributes -- ^ MMD style reference link attributes | Ext_link_attributes -- ^ MMD style reference link attributes
| Ext_autolink_bare_uris -- ^ Make all absolute URIs into links | Ext_autolink_bare_uris -- ^ Make all absolute URIs into links
| Ext_fancy_lists -- ^ Enable fancy list numbers and delimiters | Ext_fancy_lists -- ^ Enable fancy list numbers and delimiters
@ -155,6 +156,7 @@ pandocExtensions = Set.fromList
, Ext_subscript , Ext_subscript
, Ext_auto_identifiers , Ext_auto_identifiers
, Ext_header_attributes , Ext_header_attributes
, Ext_common_link_attributes
, Ext_implicit_header_references , Ext_implicit_header_references
, Ext_line_blocks , Ext_line_blocks
, Ext_shortcut_reference_links , Ext_shortcut_reference_links
@ -188,6 +190,7 @@ phpMarkdownExtraExtensions = Set.fromList
, Ext_definition_lists , Ext_definition_lists
, Ext_intraword_underscores , Ext_intraword_underscores
, Ext_header_attributes , Ext_header_attributes
, Ext_common_link_attributes
, Ext_abbreviations , Ext_abbreviations
, Ext_shortcut_reference_links , Ext_shortcut_reference_links
] ]
@ -335,6 +338,7 @@ data WriterOptions = WriterOptions
, writerSectionDivs :: Bool -- ^ Put sections in div tags in HTML , writerSectionDivs :: Bool -- ^ Put sections in div tags in HTML
, writerExtensions :: Set Extension -- ^ Markdown extensions that can be used , writerExtensions :: Set Extension -- ^ Markdown extensions that can be used
, writerReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst , writerReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
, writerDpi :: Int -- ^ Dpi for pixel to/from inch/cm conversions
, writerWrapText :: Bool -- ^ Wrap text to line length , writerWrapText :: Bool -- ^ Wrap text to line length
, writerColumns :: Int -- ^ Characters in a line (for text wrapping) , writerColumns :: Int -- ^ Characters in a line (for text wrapping)
, writerEmailObfuscation :: ObfuscationMethod -- ^ How to obfuscate emails , writerEmailObfuscation :: ObfuscationMethod -- ^ How to obfuscate emails
@ -381,6 +385,7 @@ instance Default WriterOptions where
, writerSectionDivs = False , writerSectionDivs = False
, writerExtensions = pandocExtensions , writerExtensions = pandocExtensions
, writerReferenceLinks = False , writerReferenceLinks = False
, writerDpi = 96
, writerWrapText = True , writerWrapText = True
, writerColumns = 72 , writerColumns = 72
, writerEmailObfuscation = JavascriptObfuscation , writerEmailObfuscation = JavascriptObfuscation

View file

@ -86,10 +86,10 @@ handleImage' :: WriterOptions
-> FilePath -> FilePath
-> Inline -> Inline
-> IO Inline -> IO Inline
handleImage' opts tmpdir (Image ils (src,tit)) = do handleImage' opts tmpdir (Image attr ils (src,tit)) = do
exists <- doesFileExist src exists <- doesFileExist src
if exists if exists
then return $ Image ils (src,tit) then return $ Image attr ils (src,tit)
else do else do
res <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src res <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src
case res of case res of
@ -99,20 +99,20 @@ handleImage' opts tmpdir (Image ils (src,tit)) = do
let basename = showDigest $ sha1 $ BL.fromChunks [contents] let basename = showDigest $ sha1 $ BL.fromChunks [contents]
let fname = tmpdir </> basename <.> ext let fname = tmpdir </> basename <.> ext
BS.writeFile fname contents BS.writeFile fname contents
return $ Image ils (fname,tit) return $ Image attr ils (fname,tit)
_ -> do _ -> do
warn $ "Could not find image `" ++ src ++ "', skipping..." warn $ "Could not find image `" ++ src ++ "', skipping..."
return $ Image ils (src,tit) return $ Image attr ils (src,tit)
handleImage' _ _ x = return x handleImage' _ _ x = return x
convertImages :: FilePath -> Inline -> IO Inline convertImages :: FilePath -> Inline -> IO Inline
convertImages tmpdir (Image ils (src, tit)) = do convertImages tmpdir (Image attr ils (src, tit)) = do
img <- convertImage tmpdir src img <- convertImage tmpdir src
newPath <- newPath <-
case img of case img of
Left e -> src <$ warn e Left e -> src <$ warn e
Right fp -> return fp Right fp -> return fp
return (Image ils (newPath, tit)) return (Image attr ils (newPath, tit))
convertImages _ x = return x convertImages _ x = return x
-- Convert formats which do not work well in pdf to png -- Convert formats which do not work well in pdf to png

View file

@ -164,7 +164,8 @@ module Text.Pandoc.Parsing ( anyLine,
setSourceLine, setSourceLine,
newPos, newPos,
addWarning, addWarning,
(<+?>) (<+?>),
extractIdClass
) )
where where
@ -1066,7 +1067,7 @@ toKey = Key . map toLower . unwords . words . unbracket
where unbracket ('[':xs) | "]" `isSuffixOf` xs = take (length xs - 1) xs where unbracket ('[':xs) | "]" `isSuffixOf` xs = take (length xs - 1) xs
unbracket xs = xs unbracket xs = xs
type KeyTable = M.Map Key Target type KeyTable = M.Map Key (Target, Attr)
type SubstTable = M.Map Key Inlines type SubstTable = M.Map Key Inlines
@ -1264,3 +1265,14 @@ addWarning mbpos msg =
infixr 5 <+?> infixr 5 <+?>
(<+?>) :: (Monoid a, Monad m) => ParserT s st m a -> ParserT s st m a -> ParserT s st m a (<+?>) :: (Monoid a, Monad m) => ParserT s st m a -> ParserT s st m a -> ParserT s st m a
a <+?> b = a >>= flip fmap (try b <|> return mempty) . (<>) a <+?> b = a >>= flip fmap (try b <|> return mempty) . (<>)
extractIdClass :: Attr -> Attr
extractIdClass (ident, cls, kvs) = (ident', cls', kvs')
where
ident' = case (lookup "id" kvs) of
Just v -> v
Nothing -> ident
cls' = case (lookup "class" kvs) of
Just cl -> words cl
Nothing -> cls
kvs' = filter (\(k,_) -> k /= "id" || k /= "class") kvs

View file

@ -171,7 +171,7 @@ infixr 5 $$
else x <> cr <> y else x <> cr <> y
infixr 5 $+$ infixr 5 $+$
-- | @a $$ b@ puts @a@ above @b@, with a blank line between. -- | @a $+$ b@ puts @a@ above @b@, with a blank line between.
($+$) :: Doc -> Doc -> Doc ($+$) :: Doc -> Doc -> Doc
($+$) x y = if isEmpty x ($+$) x y = if isEmpty x
then y then y

View file

@ -113,7 +113,7 @@ addInline (Node _ EMPH nodes) =
addInline (Node _ STRONG nodes) = addInline (Node _ STRONG nodes) =
(Strong (addInlines nodes) :) (Strong (addInlines nodes) :)
addInline (Node _ (LINK url title) nodes) = addInline (Node _ (LINK url title) nodes) =
(Link (addInlines nodes) (unpack url, unpack title) :) (Link nullAttr (addInlines nodes) (unpack url, unpack title) :)
addInline (Node _ (IMAGE url title) nodes) = addInline (Node _ (IMAGE url title) nodes) =
(Image (addInlines nodes) (unpack url, unpack title) :) (Image nullAttr (addInlines nodes) (unpack url, unpack title) :)
addInline _ = id addInline _ = id

View file

@ -635,11 +635,20 @@ addToStart toadd bs =
-- A DocBook mediaobject is a wrapper around a set of alternative presentations -- A DocBook mediaobject is a wrapper around a set of alternative presentations
getMediaobject :: Element -> DB Inlines getMediaobject :: Element -> DB Inlines
getMediaobject e = do getMediaobject e = do
imageUrl <- case filterChild (named "imageobject") e of (imageUrl, attr) <-
Nothing -> return mempty case filterChild (named "imageobject") e of
Nothing -> return (mempty, nullAttr)
Just z -> case filterChild (named "imagedata") z of Just z -> case filterChild (named "imagedata") z of
Nothing -> return mempty Nothing -> return (mempty, nullAttr)
Just i -> return $ attrValue "fileref" i Just i -> let atVal a = attrValue a i
w = case atVal "width" of
"" -> []
d -> [("width", d)]
h = case atVal "depth" of
"" -> []
d -> [("height", d)]
atr = (atVal "id", words $ atVal "role", w ++ h)
in return (atVal "fileref", atr)
let getCaption el = case filterChild (\x -> named "caption" x let getCaption el = case filterChild (\x -> named "caption" x
|| named "textobject" x || named "textobject" x
|| named "alt" x) el of || named "alt" x) el of
@ -649,7 +658,7 @@ getMediaobject e = do
let (caption, title) = if isNull figTitle let (caption, title) = if isNull figTitle
then (getCaption e, "") then (getCaption e, "")
else (return figTitle, "fig:") else (return figTitle, "fig:")
liftM (image imageUrl title) caption liftM (imageWith attr imageUrl title) caption
getBlocks :: Element -> DB Blocks getBlocks :: Element -> DB Blocks
getBlocks e = mconcat <$> (mapM parseBlock $ elContent e) getBlocks e = mconcat <$> (mapM parseBlock $ elContent e)
@ -968,7 +977,8 @@ parseInline (Elem e) =
Just h -> h Just h -> h
_ -> ('#' : attrValue "linkend" e) _ -> ('#' : attrValue "linkend" e)
let ils' = if ils == mempty then str href else ils let ils' = if ils == mempty then str href else ils
return $ link href "" ils' let attr = (attrValue "id" e, words $ attrValue "role" e, [])
return $ linkWith attr href "" ils'
"foreignphrase" -> emph <$> innerInlines "foreignphrase" -> emph <$> innerInlines
"emphasis" -> case attrValue "role" e of "emphasis" -> case attrValue "role" e of
"bold" -> strong <$> innerInlines "bold" -> strong <$> innerInlines

View file

@ -539,10 +539,10 @@ bodyPartToBlocks (OMathPara e) = do
-- replace targets with generated anchors. -- replace targets with generated anchors.
rewriteLink' :: Inline -> DocxContext Inline rewriteLink' :: Inline -> DocxContext Inline
rewriteLink' l@(Link ils ('#':target, title)) = do rewriteLink' l@(Link attr ils ('#':target, title)) = do
anchorMap <- gets docxAnchorMap anchorMap <- gets docxAnchorMap
return $ case M.lookup target anchorMap of return $ case M.lookup target anchorMap of
Just newTarget -> (Link ils ('#':newTarget, title)) Just newTarget -> (Link attr ils ('#':newTarget, title))
Nothing -> l Nothing -> l
rewriteLink' il = return il rewriteLink' il = return il

View file

@ -100,12 +100,12 @@ fetchImages mimes root arc (query iq -> links) =
<$> findEntryByPath abslink arc <$> findEntryByPath abslink arc
iq :: Inline -> [FilePath] iq :: Inline -> [FilePath]
iq (Image _ (url, _)) = [url] iq (Image _ _ (url, _)) = [url]
iq _ = [] iq _ = []
-- Remove relative paths -- Remove relative paths
renameImages :: FilePath -> Inline -> Inline renameImages :: FilePath -> Inline -> Inline
renameImages root (Image a (url, b)) = Image a (collapseFilePath (root </> url), b) renameImages root (Image attr a (url, b)) = Image attr a (collapseFilePath (root </> url), b)
renameImages _ x = x renameImages _ x = x
imageToPandoc :: FilePath -> Pandoc imageToPandoc :: FilePath -> Pandoc
@ -190,14 +190,14 @@ fixInlineIRs s (Span as v) =
Span (fixAttrs s as) v Span (fixAttrs s as) v
fixInlineIRs s (Code as code) = fixInlineIRs s (Code as code) =
Code (fixAttrs s as) code Code (fixAttrs s as) code
fixInlineIRs s (Link t ('#':url, tit)) = fixInlineIRs s (Link attr t ('#':url, tit)) =
Link t (addHash s url, tit) Link attr t (addHash s url, tit)
fixInlineIRs _ v = v fixInlineIRs _ v = v
prependHash :: [String] -> Inline -> Inline prependHash :: [String] -> Inline -> Inline
prependHash ps l@(Link is (url, tit)) prependHash ps l@(Link attr is (url, tit))
| or [s `isPrefixOf` url | s <- ps] = | or [s `isPrefixOf` url | s <- ps] =
Link is ('#':url, tit) Link attr is ('#':url, tit)
| otherwise = l | otherwise = l
prependHash _ i = i prependHash _ i = i

View file

@ -601,16 +601,8 @@ pLineBreak = do
return B.linebreak return B.linebreak
pLink :: TagParser Inlines pLink :: TagParser Inlines
pLink = pRelLink <|> pAnchor pLink = try $ do
tag <- pSatisfy $ tagOpenLit "a" (const True)
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"))
mbBaseHref <- baseHref <$> getState mbBaseHref <- baseHref <$> getState
let url' = fromAttrib "href" tag let url' = fromAttrib "href" tag
let url = case (isURI url', mbBaseHref) of let url = case (isURI url', mbBaseHref) of
@ -618,11 +610,9 @@ pRelLink = try $ do
_ -> url' _ -> url'
let title = fromAttrib "title" tag let title = fromAttrib "title" tag
let uid = fromAttrib "id" tag let uid = fromAttrib "id" tag
let spanC = case uid of let cls = words $ fromAttrib "class" tag
[] -> id
s -> B.spanWith (s, [], [])
lab <- trimInlines . mconcat <$> manyTill inline (pCloses "a") lab <- trimInlines . mconcat <$> manyTill inline (pCloses "a")
return $ spanC $ B.link (escapeURI url) title lab return $ B.linkWith (uid, cls, []) (escapeURI url) title lab
pImage :: TagParser Inlines pImage :: TagParser Inlines
pImage = do pImage = do
@ -634,7 +624,13 @@ pImage = do
_ -> url' _ -> url'
let title = fromAttrib "title" tag let title = fromAttrib "title" tag
let alt = fromAttrib "alt" tag let alt = fromAttrib "alt" tag
return $ B.image (escapeURI url) title (B.text alt) let uid = fromAttrib "id" tag
let cls = words $ fromAttrib "class" tag
let getAtt k = case fromAttrib k tag of
"" -> []
v -> [(k, v)]
let kvs = concat $ map getAtt ["width", "height", "sizes", "srcset"]
return $ B.imageWith (uid, cls, kvs) (escapeURI url) title (B.text alt)
pCode :: TagParser Inlines pCode :: TagParser Inlines
pCode = try $ do pCode = try $ do

View file

@ -54,6 +54,7 @@ import Data.List (intercalate)
import qualified Data.Map as M import qualified Data.Map as M
import qualified Control.Exception as E import qualified Control.Exception as E
import Text.Pandoc.Highlighting (fromListingsLanguage) import Text.Pandoc.Highlighting (fromListingsLanguage)
import Text.Pandoc.ImageSize (numUnit, showFl)
import Text.Pandoc.Error import Text.Pandoc.Error
-- | Parse LaTeX from string and return 'Pandoc' document. -- | Parse LaTeX from string and return 'Pandoc' document.
@ -398,7 +399,8 @@ inlineCommand = try $ do
star <- option "" (string "*") star <- option "" (string "*")
let name' = name ++ star let name' = name ++ star
let raw = do let raw = do
rawcommand <- getRawCommand name' rawargs <- withRaw (skipopts *> option "" dimenarg *> many braced)
let rawcommand = '\\' : name ++ star ++ snd rawargs
transformed <- applyMacros' rawcommand transformed <- applyMacros' rawcommand
if transformed /= rawcommand if transformed /= rawcommand
then parseFromString inlines transformed then parseFromString inlines transformed
@ -528,7 +530,9 @@ inlineCommands = M.fromList $
, ("href", (unescapeURL <$> braced <* optional sp) >>= \url -> , ("href", (unescapeURL <$> braced <* optional sp) >>= \url ->
tok >>= \lab -> tok >>= \lab ->
pure (link url "" lab)) pure (link url "" lab))
, ("includegraphics", skipopts *> (unescapeURL <$> braced) >>= mkImage) , ("includegraphics", do options <- option [] keyvals
src <- unescapeURL <$> braced
mkImage options src)
, ("enquote", enquote) , ("enquote", enquote)
, ("cite", citation "cite" AuthorInText False) , ("cite", citation "cite" AuthorInText False)
, ("Cite", citation "cite" AuthorInText False) , ("Cite", citation "cite" AuthorInText False)
@ -590,14 +594,19 @@ inlineCommands = M.fromList $
-- in which case they will appear as raw latex blocks: -- in which case they will appear as raw latex blocks:
[ "index" ] [ "index" ]
mkImage :: String -> LP Inlines mkImage :: [(String, String)] -> String -> LP Inlines
mkImage src = do mkImage options src = do
let replaceTextwidth (k,v) = case numUnit v of
Just (num, "\\textwidth") -> (k, showFl (num * 100) ++ "%")
_ -> (k, v)
let kvs = map replaceTextwidth $ filter (\(k,_) -> k `elem` ["width", "height"]) options
let attr = ("",[], kvs)
let alt = str "image" let alt = str "image"
case takeExtension src of case takeExtension src of
"" -> do "" -> do
defaultExt <- getOption readerDefaultImageExtension defaultExt <- getOption readerDefaultImageExtension
return $ image (addExtension src defaultExt) "" alt return $ imageWith attr (addExtension src defaultExt) "" alt
_ -> return $ image src "" alt _ -> return $ imageWith attr src "" alt
inNote :: Inlines -> Inlines inNote :: Inlines -> Inlines
inNote ils = inNote ils =
@ -978,7 +987,7 @@ readFileFromDirs (d:ds) f =
keyval :: LP (String, String) keyval :: LP (String, String)
keyval = try $ do keyval = try $ do
key <- many1 alphaNum key <- many1 alphaNum
val <- option "" $ char '=' >> many1 alphaNum val <- option "" $ char '=' >> many1 (alphaNum <|> char '.' <|> char '\\')
skipMany spaceChar skipMany spaceChar
optional (char ',') optional (char ',')
skipMany spaceChar skipMany spaceChar
@ -1005,11 +1014,11 @@ rawLaTeXInline = do
addImageCaption :: Blocks -> LP Blocks addImageCaption :: Blocks -> LP Blocks
addImageCaption = walkM go addImageCaption = walkM go
where go (Image alt (src,tit)) = do where go (Image attr alt (src,tit)) = do
mbcapt <- stateCaption <$> getState mbcapt <- stateCaption <$> getState
return $ case mbcapt of return $ case mbcapt of
Just ils -> Image (toList ils) (src, "fig:") Just ils -> Image attr (toList ils) (src, "fig:")
Nothing -> Image alt (src,tit) Nothing -> Image attr alt (src,tit)
go x = return x go x = return x
addTableCaption :: Blocks -> LP Blocks addTableCaption :: Blocks -> LP Blocks

View file

@ -368,23 +368,26 @@ referenceKey = try $ do
let sourceURL = liftM unwords $ many $ try $ do let sourceURL = liftM unwords $ many $ try $ do
skipMany spaceChar skipMany spaceChar
notFollowedBy' referenceTitle notFollowedBy' referenceTitle
notFollowedBy' $ guardEnabled Ext_common_link_attributes >> attributes
notFollowedBy' (() <$ reference) notFollowedBy' (() <$ reference)
many1 $ notFollowedBy space >> litChar many1 $ notFollowedBy space >> litChar
let betweenAngles = try $ char '<' >> manyTill litChar (char '>') let betweenAngles = try $ char '<' >> manyTill litChar (char '>')
src <- try betweenAngles <|> sourceURL src <- try betweenAngles <|> sourceURL
tit <- option "" referenceTitle tit <- option "" referenceTitle
-- currently we just ignore MMD-style link/image attributes attr <- option nullAttr $ try $
_kvs <- option [] $ guardEnabled Ext_link_attributes guardEnabled Ext_common_link_attributes >> skipSpaces >> attributes
addKvs <- option [] $ guardEnabled Ext_link_attributes
>> many (try $ spnl >> keyValAttr) >> many (try $ spnl >> keyValAttr)
blanklines blanklines
let target = (escapeURI $ trimr src, tit) let attr' = extractIdClass $ foldl (\x f -> f x) attr addKvs
target = (escapeURI $ trimr src, tit)
st <- getState st <- getState
let oldkeys = stateKeys st let oldkeys = stateKeys st
let key = toKey raw let key = toKey raw
case M.lookup key oldkeys of case M.lookup key oldkeys of
Just _ -> addWarning (Just pos) $ "Duplicate link reference `" ++ raw ++ "'" Just _ -> addWarning (Just pos) $ "Duplicate link reference `" ++ raw ++ "'"
Nothing -> return () Nothing -> return ()
updateState $ \s -> s { stateKeys = M.insert key target oldkeys } updateState $ \s -> s { stateKeys = M.insert key (target, attr') oldkeys }
return $ return mempty return $ return mempty
referenceTitle :: MarkdownParser String referenceTitle :: MarkdownParser String
@ -517,9 +520,9 @@ atxHeader = try $ do
(text, raw) <- withRaw $ (text, raw) <- withRaw $
trimInlinesF . mconcat <$> many (notFollowedBy atxClosing >> inline) trimInlinesF . mconcat <$> many (notFollowedBy atxClosing >> inline)
attr <- atxClosing attr <- atxClosing
attr'@(ident,_,_) <- registerHeader attr (runF text defaultParserState) attr' <- registerHeader attr (runF text defaultParserState)
guardDisabled Ext_implicit_header_references guardDisabled Ext_implicit_header_references
<|> registerImplicitHeader raw ident <|> registerImplicitHeader raw attr'
return $ B.headerWith attr' level <$> text return $ B.headerWith attr' level <$> text
atxClosing :: MarkdownParser Attr atxClosing :: MarkdownParser Attr
@ -560,16 +563,16 @@ setextHeader = try $ do
many (char underlineChar) many (char underlineChar)
blanklines blanklines
let level = (fromMaybe 0 $ findIndex (== underlineChar) setextHChars) + 1 let level = (fromMaybe 0 $ findIndex (== underlineChar) setextHChars) + 1
attr'@(ident,_,_) <- registerHeader attr (runF text defaultParserState) attr' <- registerHeader attr (runF text defaultParserState)
guardDisabled Ext_implicit_header_references guardDisabled Ext_implicit_header_references
<|> registerImplicitHeader raw ident <|> registerImplicitHeader raw attr'
return $ B.headerWith attr' level <$> text return $ B.headerWith attr' level <$> text
registerImplicitHeader :: String -> String -> MarkdownParser () registerImplicitHeader :: String -> Attr -> MarkdownParser ()
registerImplicitHeader raw ident = do registerImplicitHeader raw attr@(ident, _, _) = do
let key = toKey $ "[" ++ raw ++ "]" let key = toKey $ "[" ++ raw ++ "]"
updateState (\s -> s { stateHeaderKeys = updateState (\s -> s { stateHeaderKeys =
M.insert key ('#':ident,"") (stateHeaderKeys s) }) M.insert key (('#':ident,""), attr) (stateHeaderKeys s) })
-- --
-- hrule block -- hrule block
@ -980,11 +983,11 @@ para = try $ do
return $ do return $ do
result' <- result result' <- result
case B.toList result' of case B.toList result' of
[Image alt (src,tit)] [Image attr alt (src,tit)]
| Ext_implicit_figures `Set.member` exts -> | Ext_implicit_figures `Set.member` exts ->
-- the fig: at beginning of title indicates a figure -- the fig: at beginning of title indicates a figure
return $ B.para $ B.singleton return $ B.para $ B.singleton
$ Image alt (src,'f':'i':'g':':':tit) $ Image attr alt (src,'f':'i':'g':':':tit)
_ -> return $ B.para result' _ -> return $ B.para result'
plain :: MarkdownParser (F Blocks) plain :: MarkdownParser (F Blocks)
@ -1719,16 +1722,18 @@ link = try $ do
setState $ st{ stateAllowLinks = False } setState $ st{ stateAllowLinks = False }
(lab,raw) <- reference (lab,raw) <- reference
setState $ st{ stateAllowLinks = True } setState $ st{ stateAllowLinks = True }
regLink B.link lab <|> referenceLink B.link (lab,raw) regLink B.linkWith lab <|> referenceLink B.linkWith (lab,raw)
regLink :: (String -> String -> Inlines -> Inlines) regLink :: (Attr -> String -> String -> Inlines -> Inlines)
-> F Inlines -> MarkdownParser (F Inlines) -> F Inlines -> MarkdownParser (F Inlines)
regLink constructor lab = try $ do regLink constructor lab = try $ do
(src, tit) <- source (src, tit) <- source
return $ constructor src tit <$> lab attr <- option nullAttr $
guardEnabled Ext_common_link_attributes >> attributes
return $ constructor attr src tit <$> lab
-- a link like [this][ref] or [this][] or [this] -- a link like [this][ref] or [this][] or [this]
referenceLink :: (String -> String -> Inlines -> Inlines) referenceLink :: (Attr -> String -> String -> Inlines -> Inlines)
-> (F Inlines, String) -> MarkdownParser (F Inlines) -> (F Inlines, String) -> MarkdownParser (F Inlines)
referenceLink constructor (lab, raw) = do referenceLink constructor (lab, raw) = do
sp <- (True <$ lookAhead (char ' ')) <|> return False sp <- (True <$ lookAhead (char ' ')) <|> return False
@ -1757,10 +1762,10 @@ referenceLink constructor (lab, raw) = do
then do then do
headerKeys <- asksF stateHeaderKeys headerKeys <- asksF stateHeaderKeys
case M.lookup key headerKeys of case M.lookup key headerKeys of
Just (src, tit) -> constructor src tit <$> lab Just ((src, tit), _) -> constructor nullAttr src tit <$> lab
Nothing -> makeFallback Nothing -> makeFallback
else makeFallback else makeFallback
Just (src,tit) -> constructor src tit <$> lab Just ((src,tit), attr) -> constructor attr src tit <$> lab
dropBrackets :: String -> String dropBrackets :: String -> String
dropBrackets = reverse . dropRB . reverse . dropLB dropBrackets = reverse . dropRB . reverse . dropLB
@ -1794,9 +1799,9 @@ image = try $ do
char '!' char '!'
(lab,raw) <- reference (lab,raw) <- reference
defaultExt <- getOption readerDefaultImageExtension defaultExt <- getOption readerDefaultImageExtension
let constructor src = case takeExtension src of let constructor attr' src = case takeExtension src of
"" -> B.image (addExtension src defaultExt) "" -> B.imageWith attr' (addExtension src defaultExt)
_ -> B.image src _ -> B.imageWith attr' src
regLink constructor lab <|> referenceLink constructor (lab,raw) regLink constructor lab <|> referenceLink constructor (lab,raw)
note :: MarkdownParser (F Inlines) note :: MarkdownParser (F Inlines)
@ -1947,7 +1952,7 @@ textualCite = try $ do
spc | null spaces' = mempty spc | null spaces' = mempty
| otherwise = B.space | otherwise = B.space
lab <- parseFromString (mconcat <$> many inline) $ dropBrackets raw' lab <- parseFromString (mconcat <$> many inline) $ dropBrackets raw'
fallback <- referenceLink B.link (lab,raw') fallback <- referenceLink B.linkWith (lab,raw')
return $ do return $ do
fallback' <- fallback fallback' <- fallback
cs' <- cs cs' <- cs

View file

@ -576,20 +576,28 @@ image = try $ do
sym "[[" sym "[["
choice imageIdentifiers choice imageIdentifiers
fname <- many1 (noneOf "|]") fname <- many1 (noneOf "|]")
_ <- many (try $ char '|' *> imageOption) _ <- many imageOption
dims <- try (char '|' *> (sepBy (many digit) (char 'x')) <* string "px")
<|> return []
_ <- many imageOption
let kvs = case dims of
w:[] -> [("width", w)]
w:(h:[]) -> [("width", w), ("height", h)]
_ -> []
let attr = ("", [], kvs)
caption <- (B.str fname <$ sym "]]") caption <- (B.str fname <$ sym "]]")
<|> try (char '|' *> (mconcat <$> manyTill inline (sym "]]"))) <|> try (char '|' *> (mconcat <$> manyTill inline (sym "]]")))
return $ B.image fname ("fig:" ++ stringify caption) caption return $ B.imageWith attr fname ("fig:" ++ stringify caption) caption
imageOption :: MWParser String imageOption :: MWParser String
imageOption = imageOption = try $ char '|' *> opt
try (oneOfStrings [ "border", "thumbnail", "frameless" where
opt = try (oneOfStrings [ "border", "thumbnail", "frameless"
, "thumb", "upright", "left", "right" , "thumb", "upright", "left", "right"
, "center", "none", "baseline", "sub" , "center", "none", "baseline", "sub"
, "super", "top", "text-top", "middle" , "super", "top", "text-top", "middle"
, "bottom", "text-bottom" ]) , "bottom", "text-bottom" ])
<|> try (string "frame") <|> try (string "frame")
<|> try (many1 (oneOf "x0123456789") <* string "px")
<|> try (oneOfStrings ["link=","alt=","page=","class="] <* many (noneOf "|]")) <|> try (oneOfStrings ["link=","alt=","page=","class="] <* many (noneOf "|]"))
collapseUnderscores :: String -> String collapseUnderscores :: String -> String

View file

@ -812,9 +812,9 @@ substKey = try $ do
res <- B.toList <$> directive' res <- B.toList <$> directive'
il <- case res of il <- case res of
-- use alt unless :alt: attribute on image: -- use alt unless :alt: attribute on image:
[Para [Image [Str "image"] (src,tit)]] -> [Para [Image _ [Str "image"] (src,tit)]] ->
return $ B.image src tit alt return $ B.image src tit alt
[Para [Link [Image [Str "image"] (src,tit)] (src',tit')]] -> [Para [Link _ [Image _ [Str "image"] (src,tit)] (src',tit')]] ->
return $ B.link src' tit' (B.image src tit alt) return $ B.link src' tit' (B.image src tit alt)
[Para ils] -> return $ B.fromList ils [Para ils] -> return $ B.fromList ils
_ -> mzero _ -> mzero
@ -827,7 +827,8 @@ anonymousKey = try $ do
src <- targetURI src <- targetURI
pos <- getPosition pos <- getPosition
let key = toKey $ "_" ++ printf "%09d" (sourceLine pos) let key = toKey $ "_" ++ printf "%09d" (sourceLine pos)
updateState $ \s -> s { stateKeys = M.insert key (src,"") $ stateKeys s } --TODO: parse width, height, class and name attributes
updateState $ \s -> s { stateKeys = M.insert key ((src,""), nullAttr) $ stateKeys s }
stripTicks :: String -> String stripTicks :: String -> String
stripTicks = reverse . stripTick . reverse . stripTick stripTicks = reverse . stripTick . reverse . stripTick
@ -841,7 +842,8 @@ regularKey = try $ do
char ':' char ':'
src <- targetURI src <- targetURI
let key = toKey $ stripTicks ref let key = toKey $ stripTicks ref
updateState $ \s -> s { stateKeys = M.insert key (src,"") $ stateKeys s } --TODO: parse width, height, class and name attributes
updateState $ \s -> s { stateKeys = M.insert key ((src,""), nullAttr) $ stateKeys s }
-- --
-- tables -- tables
@ -1131,12 +1133,12 @@ referenceLink = try $ do
if null anonKeys if null anonKeys
then mzero then mzero
else return (head anonKeys) else return (head anonKeys)
(src,tit) <- case M.lookup key keyTable of ((src,tit), attr) <- case M.lookup key keyTable of
Nothing -> fail "no corresponding key" Nothing -> fail "no corresponding key"
Just target -> return target Just val -> return val
-- if anonymous link, remove key so it won't be used again -- if anonymous link, remove key so it won't be used again
when (isAnonKey key) $ updateState $ \s -> s{ stateKeys = M.delete key keyTable } when (isAnonKey key) $ updateState $ \s -> s{ stateKeys = M.delete key keyTable }
return $ B.link src tit label' return $ B.linkWith attr src tit label'
autoURI :: RSTParser Inlines autoURI :: RSTParser Inlines
autoURI = do autoURI = do

View file

@ -523,10 +523,10 @@ normalizeInlines (Note bs : ys) = Note (normalizeBlocks bs) :
normalizeInlines ys normalizeInlines ys
normalizeInlines (Quoted qt ils : ys) = normalizeInlines (Quoted qt ils : ys) =
Quoted qt (normalizeInlines ils) : normalizeInlines ys Quoted qt (normalizeInlines ils) : normalizeInlines ys
normalizeInlines (Link ils t : ys) = normalizeInlines (Link attr ils t : ys) =
Link (normalizeInlines ils) t : normalizeInlines ys Link attr (normalizeInlines ils) t : normalizeInlines ys
normalizeInlines (Image ils t : ys) = normalizeInlines (Image attr ils t : ys) =
Image (normalizeInlines ils) t : normalizeInlines ys Image attr (normalizeInlines ils) t : normalizeInlines ys
normalizeInlines (Cite cs ils : ys) = normalizeInlines (Cite cs ils : ys) =
Cite cs (normalizeInlines ils) : normalizeInlines ys Cite cs (normalizeInlines ils) : normalizeInlines ys
normalizeInlines (x : xs) = x : normalizeInlines xs normalizeInlines (x : xs) = x : normalizeInlines xs

View file

@ -46,6 +46,7 @@ import Text.Pandoc.Parsing hiding (blankline, space)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
import Data.List ( stripPrefix, intersperse, intercalate ) import Data.List ( stripPrefix, intersperse, intercalate )
import Text.Pandoc.Pretty import Text.Pandoc.Pretty
import Text.Pandoc.ImageSize
import Control.Monad.State import Control.Monad.State
import qualified Data.Map as M import qualified Data.Map as M
import Data.Aeson (Value(String), fromJSON, toJSON, Result(..)) import Data.Aeson (Value(String), fromJSON, toJSON, Result(..))
@ -126,8 +127,8 @@ blockToAsciiDoc _ Null = return empty
blockToAsciiDoc opts (Plain inlines) = do blockToAsciiDoc opts (Plain inlines) = do
contents <- inlineListToAsciiDoc opts inlines contents <- inlineListToAsciiDoc opts inlines
return $ contents <> blankline return $ contents <> blankline
blockToAsciiDoc opts (Para [Image alt (src,'f':'i':'g':':':tit)]) = do blockToAsciiDoc opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = do
blockToAsciiDoc opts (Para [Image alt (src,tit)]) blockToAsciiDoc opts (Para [Image attr alt (src,tit)])
blockToAsciiDoc opts (Para inlines) = do blockToAsciiDoc opts (Para inlines) = do
contents <- inlineListToAsciiDoc opts inlines contents <- inlineListToAsciiDoc opts inlines
-- escape if para starts with ordered list marker -- escape if para starts with ordered list marker
@ -392,7 +393,7 @@ inlineToAsciiDoc _ (RawInline f s)
inlineToAsciiDoc _ (LineBreak) = return $ " +" <> cr inlineToAsciiDoc _ (LineBreak) = return $ " +" <> cr
inlineToAsciiDoc _ Space = return space inlineToAsciiDoc _ Space = return space
inlineToAsciiDoc opts (Cite _ lst) = inlineListToAsciiDoc opts lst inlineToAsciiDoc opts (Cite _ lst) = inlineListToAsciiDoc opts lst
inlineToAsciiDoc opts (Link txt (src, _tit)) = do inlineToAsciiDoc opts (Link _ txt (src, _tit)) = do
-- relative: link:downloads/foo.zip[download foo.zip] -- relative: link:downloads/foo.zip[download foo.zip]
-- abs: http://google.cod[Google] -- abs: http://google.cod[Google]
-- or my@email.com[email john] -- or my@email.com[email john]
@ -408,7 +409,7 @@ inlineToAsciiDoc opts (Link txt (src, _tit)) = do
return $ if useAuto return $ if useAuto
then text srcSuffix then text srcSuffix
else prefix <> text src <> "[" <> linktext <> "]" else prefix <> text src <> "[" <> linktext <> "]"
inlineToAsciiDoc opts (Image alternate (src, tit)) = do inlineToAsciiDoc opts (Image attr alternate (src, tit)) = do
-- image:images/logo.png[Company logo, title="blah"] -- image:images/logo.png[Company logo, title="blah"]
let txt = if (null alternate) || (alternate == [Str ""]) let txt = if (null alternate) || (alternate == [Str ""])
then [Str "image"] then [Str "image"]
@ -416,8 +417,19 @@ inlineToAsciiDoc opts (Image alternate (src, tit)) = do
linktext <- inlineListToAsciiDoc opts txt linktext <- inlineListToAsciiDoc opts txt
let linktitle = if null tit let linktitle = if null tit
then empty then empty
else text $ ",title=\"" ++ tit ++ "\"" else ",title=\"" <> text tit <> "\""
return $ "image:" <> text src <> "[" <> linktext <> linktitle <> "]" showDim dir = case (dimension dir attr) of
Just (Percent a) ->
["scaledwidth=" <> text (show (Percent a))]
Just dim ->
[text (show dir) <> "=" <> text (showInPixel opts dim)]
Nothing ->
[]
dimList = showDim Width ++ showDim Height
dims = if null dimList
then empty
else "," <> cat (intersperse "," dimList)
return $ "image:" <> text src <> "[" <> linktext <> linktitle <> dims <> "]"
inlineToAsciiDoc opts (Note [Para inlines]) = inlineToAsciiDoc opts (Note [Para inlines]) =
inlineToAsciiDoc opts (Note [Plain inlines]) inlineToAsciiDoc opts (Note [Plain inlines])
inlineToAsciiDoc opts (Note [Plain inlines]) = do inlineToAsciiDoc opts (Note [Plain inlines]) = do

View file

@ -153,9 +153,9 @@ inlineToNodes (SmallCaps xs) =
((node (INLINE_HTML (T.pack "<span style=\"font-variant:small-caps;\">")) [] ((node (INLINE_HTML (T.pack "<span style=\"font-variant:small-caps;\">")) []
: inlinesToNodes xs ++ : inlinesToNodes xs ++
[node (INLINE_HTML (T.pack "</span>")) []]) ++ ) [node (INLINE_HTML (T.pack "</span>")) []]) ++ )
inlineToNodes (Link ils (url,tit)) = inlineToNodes (Link _ ils (url,tit)) =
(node (LINK (T.pack url) (T.pack tit)) (inlinesToNodes ils) :) (node (LINK (T.pack url) (T.pack tit)) (inlinesToNodes ils) :)
inlineToNodes (Image ils (url,tit)) = inlineToNodes (Image _ ils (url,tit)) =
(node (IMAGE (T.pack url) (T.pack tit)) (inlinesToNodes ils) :) (node (IMAGE (T.pack url) (T.pack tit)) (inlinesToNodes ils) :)
inlineToNodes (RawInline fmt xs) inlineToNodes (RawInline fmt xs)
| fmt == Format "html" = (node (INLINE_HTML (T.pack xs)) [] :) | fmt == Format "html" = (node (INLINE_HTML (T.pack xs)) [] :)

View file

@ -35,10 +35,11 @@ import Text.Pandoc.Writers.Shared
import Text.Pandoc.Options import Text.Pandoc.Options
import Text.Pandoc.Walk (query) import Text.Pandoc.Walk (query)
import Text.Printf ( printf ) import Text.Printf ( printf )
import Data.List ( intercalate ) import Data.List ( intercalate, intersperse )
import Data.Char ( ord ) import Data.Char ( ord )
import Control.Monad.State import Control.Monad.State
import Text.Pandoc.Pretty import Text.Pandoc.Pretty
import Text.Pandoc.ImageSize
import Text.Pandoc.Templates ( renderTemplate' ) import Text.Pandoc.Templates ( renderTemplate' )
import Network.URI ( isURI, unEscapeString ) import Network.URI ( isURI, unEscapeString )
@ -141,10 +142,14 @@ blockToConTeXt :: Block
blockToConTeXt Null = return empty blockToConTeXt Null = return empty
blockToConTeXt (Plain lst) = inlineListToConTeXt lst blockToConTeXt (Plain lst) = inlineListToConTeXt lst
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
blockToConTeXt (Para [Image txt (src,'f':'i':'g':':':_)]) = do blockToConTeXt (Para [Image attr txt (src,'f':'i':'g':':':_)]) = do
capt <- inlineListToConTeXt txt capt <- inlineListToConTeXt txt
return $ blankline $$ "\\placefigure" <> braces capt <> img <- inlineToConTeXt (Image attr txt (src, ""))
braces ("\\externalfigure" <> brackets (text src)) <> blankline let (ident, _, _) = attr
label = if null ident
then empty
else "[]" <> brackets (text $ toLabel ident)
return $ blankline $$ "\\placefigure" <> label <> braces capt <> img <> blankline
blockToConTeXt (Para lst) = do blockToConTeXt (Para lst) = do
contents <- inlineListToConTeXt lst contents <- inlineListToConTeXt lst
return $ contents <> blankline return $ contents <> blankline
@ -312,7 +317,7 @@ inlineToConTeXt (RawInline _ _) = return empty
inlineToConTeXt (LineBreak) = return $ text "\\crlf" <> cr inlineToConTeXt (LineBreak) = return $ text "\\crlf" <> cr
inlineToConTeXt Space = return space inlineToConTeXt Space = return space
-- Handle HTML-like internal document references to sections -- Handle HTML-like internal document references to sections
inlineToConTeXt (Link txt (('#' : ref), _)) = do inlineToConTeXt (Link _ txt (('#' : ref), _)) = do
opts <- gets stOptions opts <- gets stOptions
contents <- inlineListToConTeXt txt contents <- inlineListToConTeXt txt
let ref' = toLabel $ stringToConTeXt opts ref let ref' = toLabel $ stringToConTeXt opts ref
@ -320,7 +325,7 @@ inlineToConTeXt (Link txt (('#' : ref), _)) = do
<> braces contents <> braces contents
<> brackets (text ref') <> brackets (text ref')
inlineToConTeXt (Link txt (src, _)) = do inlineToConTeXt (Link _ txt (src, _)) = do
let isAutolink = txt == [Str (unEscapeString src)] let isAutolink = txt == [Str (unEscapeString src)]
st <- get st <- get
let next = stNextRef st let next = stNextRef st
@ -335,11 +340,29 @@ inlineToConTeXt (Link txt (src, _)) = do
else brackets empty <> brackets contents) else brackets empty <> brackets contents)
<> "\\from" <> "\\from"
<> brackets (text ref) <> brackets (text ref)
inlineToConTeXt (Image _ (src, _)) = do inlineToConTeXt (Image attr@(_,cls,_) _ (src, _)) = do
let src' = if isURI src opts <- gets stOptions
let showDim dir = let d = text (show dir) <> "="
in case (dimension dir attr) of
Just (Pixel a) ->
[d <> text (showInInch opts (Pixel a)) <> "in"]
Just (Percent a) ->
[d <> text (showFl (a / 100)) <> "\\textwidth"]
Just dim ->
[d <> text (show dim)]
Nothing ->
[]
dimList = showDim Width ++ showDim Height
dims = if null dimList
then empty
else brackets $ cat (intersperse "," dimList)
clas = if null cls
then empty
else brackets $ text $ toLabel $ head cls
src' = if isURI src
then src then src
else unEscapeString src else unEscapeString src
return $ braces $ "\\externalfigure" <> brackets (text src') return $ braces $ "\\externalfigure" <> brackets (text src') <> dims <> clas
inlineToConTeXt (Note contents) = do inlineToConTeXt (Note contents) = do
contents' <- blockListToConTeXt contents contents' <- blockListToConTeXt contents
let codeBlock x@(CodeBlock _ _) = [x] let codeBlock x@(CodeBlock _ _) = [x]

View file

@ -222,7 +222,7 @@ blockToCustom _ Null = return ""
blockToCustom lua (Plain inlines) = callfunc lua "Plain" inlines blockToCustom lua (Plain inlines) = callfunc lua "Plain" inlines
blockToCustom lua (Para [Image txt (src,tit)]) = blockToCustom lua (Para [Image _ txt (src,tit)]) =
callfunc lua "CaptionedImage" src tit txt callfunc lua "CaptionedImage" src tit txt
blockToCustom lua (Para inlines) = callfunc lua "Para" inlines blockToCustom lua (Para inlines) = callfunc lua "Para" inlines
@ -308,10 +308,10 @@ inlineToCustom lua (RawInline format str) =
inlineToCustom lua (LineBreak) = callfunc lua "LineBreak" inlineToCustom lua (LineBreak) = callfunc lua "LineBreak"
inlineToCustom lua (Link txt (src,tit)) = inlineToCustom lua (Link _ txt (src,tit)) =
callfunc lua "Link" txt src tit callfunc lua "Link" txt src tit
inlineToCustom lua (Image alt (src,tit)) = inlineToCustom lua (Image _ alt (src,tit)) =
callfunc lua "Image" alt src tit callfunc lua "Image" alt src tit
inlineToCustom lua (Note contents) = callfunc lua "Note" contents inlineToCustom lua (Note contents) = callfunc lua "Note" contents

View file

@ -42,6 +42,7 @@ import Data.Char ( toLower )
import Data.Monoid ( Any(..) ) import Data.Monoid ( Any(..) )
import Text.Pandoc.Highlighting ( languages, languagesByExtension ) import Text.Pandoc.Highlighting ( languages, languagesByExtension )
import Text.Pandoc.Pretty import Text.Pandoc.Pretty
import Text.Pandoc.ImageSize
import qualified Text.Pandoc.Builder as B import qualified Text.Pandoc.Builder as B
import Text.TeXMath import Text.TeXMath
import qualified Text.XML.Light as Xml import qualified Text.XML.Light as Xml
@ -150,6 +151,15 @@ listItemToDocbook :: WriterOptions -> [Block] -> Doc
listItemToDocbook opts item = listItemToDocbook opts item =
inTagsIndented "listitem" $ blocksToDocbook opts $ map plainToPara item inTagsIndented "listitem" $ blocksToDocbook opts $ map plainToPara item
imageToDocbook :: WriterOptions -> Attr -> String -> Doc
imageToDocbook _ attr src = selfClosingTag "imagedata" $
("fileref", src) : idAndRole attr ++ dims
where
dims = go Width "width" ++ go Height "depth"
go dir dstr = case (dimension dir attr) of
Just a -> [(dstr, show a)]
Nothing -> []
-- | Convert a Pandoc block element to Docbook. -- | Convert a Pandoc block element to Docbook.
blockToDocbook :: WriterOptions -> Block -> Doc blockToDocbook :: WriterOptions -> Block -> Doc
blockToDocbook _ Null = empty blockToDocbook _ Null = empty
@ -165,7 +175,7 @@ blockToDocbook opts (Div _ bs) = blocksToDocbook opts $ map plainToPara bs
blockToDocbook _ (Header _ _ _) = empty -- should not occur after hierarchicalize blockToDocbook _ (Header _ _ _) = empty -- should not occur after hierarchicalize
blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
blockToDocbook opts (Para [Image txt (src,'f':'i':'g':':':_)]) = blockToDocbook opts (Para [Image attr txt (src,'f':'i':'g':':':_)]) =
let alt = inlinesToDocbook opts txt let alt = inlinesToDocbook opts txt
capt = if null txt capt = if null txt
then empty then empty
@ -174,7 +184,7 @@ blockToDocbook opts (Para [Image txt (src,'f':'i':'g':':':_)]) =
capt $$ capt $$
(inTagsIndented "mediaobject" $ (inTagsIndented "mediaobject" $
(inTagsIndented "imageobject" (inTagsIndented "imageobject"
(selfClosingTag "imagedata" [("fileref",src)])) $$ (imageToDocbook opts attr src)) $$
inTagsSimple "textobject" (inTagsSimple "phrase" alt)) inTagsSimple "textobject" (inTagsSimple "phrase" alt))
blockToDocbook opts (Para lst) blockToDocbook opts (Para lst)
| hasLineBreaks lst = flush $ nowrap $ inTagsSimple "literallayout" $ inlinesToDocbook opts lst | hasLineBreaks lst = flush $ nowrap $ inTagsSimple "literallayout" $ inlinesToDocbook opts lst
@ -321,7 +331,7 @@ inlineToDocbook _ (RawInline f x) | f == "html" || f == "docbook" = text x
| otherwise = empty | otherwise = empty
inlineToDocbook _ LineBreak = text "\n" inlineToDocbook _ LineBreak = text "\n"
inlineToDocbook _ Space = space inlineToDocbook _ Space = space
inlineToDocbook opts (Link txt (src, _)) inlineToDocbook opts (Link attr txt (src, _))
| Just email <- stripPrefix "mailto:" src = | Just email <- stripPrefix "mailto:" src =
let emailLink = inTagsSimple "email" $ text $ let emailLink = inTagsSimple "email" $ text $
escapeStringForXML $ email escapeStringForXML $ email
@ -331,19 +341,30 @@ inlineToDocbook opts (Link txt (src, _))
char '(' <> emailLink <> char ')' char '(' <> emailLink <> char ')'
| otherwise = | otherwise =
(if isPrefixOf "#" src (if isPrefixOf "#" src
then inTags False "link" [("linkend", drop 1 src)] then inTags False "link" $ ("linkend", drop 1 src) : idAndRole attr
else inTags False "ulink" [("url", src)]) $ else inTags False "ulink" $ ("url", src) : idAndRole attr ) $
inlinesToDocbook opts txt inlinesToDocbook opts txt
inlineToDocbook _ (Image _ (src, tit)) = inlineToDocbook opts (Image attr _ (src, tit)) =
let titleDoc = if null tit let titleDoc = if null tit
then empty then empty
else inTagsIndented "objectinfo" $ else inTagsIndented "objectinfo" $
inTagsIndented "title" (text $ escapeStringForXML tit) inTagsIndented "title" (text $ escapeStringForXML tit)
in inTagsIndented "inlinemediaobject" $ inTagsIndented "imageobject" $ in inTagsIndented "inlinemediaobject" $ inTagsIndented "imageobject" $
titleDoc $$ selfClosingTag "imagedata" [("fileref", src)] titleDoc $$ imageToDocbook opts attr src
inlineToDocbook opts (Note contents) = inlineToDocbook opts (Note contents) =
inTagsIndented "footnote" $ blocksToDocbook opts contents inTagsIndented "footnote" $ blocksToDocbook opts contents
isMathML :: HTMLMathMethod -> Bool isMathML :: HTMLMathMethod -> Bool
isMathML (MathML _) = True isMathML (MathML _) = True
isMathML _ = False isMathML _ = False
idAndRole :: Attr -> [(String, String)]
idAndRole (id',cls,_) = ident ++ role
where
ident = if null id'
then []
else [("id", id')]
role = if null cls
then []
else [("role", unwords cls)]

View file

@ -536,7 +536,6 @@ styleToOpenXml sm style =
, mknode "w:link" [("w:val","VerbatimChar")] () , mknode "w:link" [("w:val","VerbatimChar")] ()
, mknode "w:pPr" [] , mknode "w:pPr" []
$ mknode "w:wordWrap" [("w:val","off")] () $ mknode "w:wordWrap" [("w:val","off")] ()
: mknode "w:noProof" [] ()
: ( maybe [] (\col -> [mknode "w:shd" [("w:val","clear"),("w:fill",drop 1 $ fromColor col)] ()]) : ( maybe [] (\col -> [mknode "w:shd" [("w:val","clear"),("w:fill",drop 1 $ fromColor col)] ()])
$ backgroundColor style ) $ backgroundColor style )
] ]
@ -752,7 +751,7 @@ blockToOpenXML opts (Header lev (ident,_,_) lst) = do
blockToOpenXML opts (Plain lst) = withParaProp (pCustomStyle "Compact") blockToOpenXML opts (Plain lst) = withParaProp (pCustomStyle "Compact")
$ blockToOpenXML opts (Para lst) $ blockToOpenXML opts (Para lst)
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
blockToOpenXML opts (Para [Image alt (src,'f':'i':'g':':':tit)]) = do blockToOpenXML opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = do
setFirstPara setFirstPara
pushParaProp $ pCustomStyle $ pushParaProp $ pCustomStyle $
if null alt if null alt
@ -760,7 +759,7 @@ blockToOpenXML opts (Para [Image alt (src,'f':'i':'g':':':tit)]) = do
else "FigureWithCaption" else "FigureWithCaption"
paraProps <- getParaProps False paraProps <- getParaProps False
popParaProp popParaProp
contents <- inlinesToOpenXML opts [Image alt (src,tit)] contents <- inlinesToOpenXML opts [Image attr alt (src,tit)]
captionNode <- withParaProp (pCustomStyle "ImageCaption") captionNode <- withParaProp (pCustomStyle "ImageCaption")
$ blockToOpenXML opts (Para alt) $ blockToOpenXML opts (Para alt)
return $ mknode "w:p" [] (paraProps ++ contents) : captionNode return $ mknode "w:p" [] (paraProps ++ contents) : captionNode
@ -1087,11 +1086,11 @@ inlineToOpenXML opts (Note bs) = do
[ mknode "w:rPr" [] footnoteStyle [ mknode "w:rPr" [] footnoteStyle
, mknode "w:footnoteReference" [("w:id", notenum)] () ] ] , mknode "w:footnoteReference" [("w:id", notenum)] () ] ]
-- internal link: -- internal link:
inlineToOpenXML opts (Link txt ('#':xs,_)) = do inlineToOpenXML opts (Link _ txt ('#':xs,_)) = do
contents <- withTextPropM (rStyleM "Hyperlink") $ inlinesToOpenXML opts txt contents <- withTextPropM (rStyleM "Hyperlink") $ inlinesToOpenXML opts txt
return [ mknode "w:hyperlink" [("w:anchor",xs)] contents ] return [ mknode "w:hyperlink" [("w:anchor",xs)] contents ]
-- external link: -- external link:
inlineToOpenXML opts (Link txt (src,_)) = do inlineToOpenXML opts (Link _ txt (src,_)) = do
contents <- withTextPropM (rStyleM "Hyperlink") $ inlinesToOpenXML opts txt contents <- withTextPropM (rStyleM "Hyperlink") $ inlinesToOpenXML opts txt
extlinks <- gets stExternalLinks extlinks <- gets stExternalLinks
id' <- case M.lookup src extlinks of id' <- case M.lookup src extlinks of
@ -1102,7 +1101,7 @@ inlineToOpenXML opts (Link txt (src,_)) = do
M.insert src i extlinks } M.insert src i extlinks }
return i return i
return [ mknode "w:hyperlink" [("r:id",id')] contents ] return [ mknode "w:hyperlink" [("r:id",id')] contents ]
inlineToOpenXML opts (Image alt (src, tit)) = do inlineToOpenXML opts (Image attr alt (src, tit)) = do
-- first, check to see if we've already done this image -- first, check to see if we've already done this image
pageWidth <- gets stPrintWidth pageWidth <- gets stPrintWidth
imgs <- gets stImages imgs <- gets stImages
@ -1119,7 +1118,8 @@ inlineToOpenXML opts (Image alt (src, tit)) = do
Right (img, mt) -> do Right (img, mt) -> do
ident <- ("rId"++) `fmap` getUniqueId ident <- ("rId"++) `fmap` getUniqueId
(xpt,ypt) <- case imageSize img of (xpt,ypt) <- case imageSize img of
Right size -> return $ sizeInPoints size Right size -> return $
desiredSizeInPoints opts attr size
Left msg -> do Left msg -> do
liftIO $ warn $ liftIO $ warn $
"Could not determine image size in `" ++ "Could not determine image size in `" ++
@ -1211,11 +1211,9 @@ parseXml refArchive distArchive relpath =
-- | Scales the image to fit the page -- | Scales the image to fit the page
-- sizes are passed in emu -- sizes are passed in emu
fitToPage :: (Integer, Integer) -> Integer -> (Integer, Integer) fitToPage :: (Double, Double) -> Integer -> (Integer, Integer)
fitToPage (x, y) pageWidth fitToPage (x, y) pageWidth
-- Fixes width to the page width and scales the height -- Fixes width to the page width and scales the height
| x > pageWidth = | x > fromIntegral pageWidth =
(pageWidth, round $ (pageWidth, floor $ ((fromIntegral pageWidth) / x) * y)
((fromIntegral pageWidth) / ((fromIntegral :: Integer -> Double) x)) * (fromIntegral y)) | otherwise = (floor x, floor y)
| otherwise = (x, y)

View file

@ -47,6 +47,7 @@ import Text.Pandoc.Options ( WriterOptions(
import Text.Pandoc.Shared ( escapeURI, removeFormatting, camelCaseToHyphenated import Text.Pandoc.Shared ( escapeURI, removeFormatting, camelCaseToHyphenated
, trimr, normalize, substitute ) , trimr, normalize, substitute )
import Text.Pandoc.Writers.Shared ( defField, metaToJSON ) import Text.Pandoc.Writers.Shared ( defField, metaToJSON )
import Text.Pandoc.ImageSize
import Text.Pandoc.Templates ( renderTemplate' ) import Text.Pandoc.Templates ( renderTemplate' )
import Data.List ( intersect, intercalate, isPrefixOf, transpose ) import Data.List ( intersect, intercalate, isPrefixOf, transpose )
import Data.Default (Default(..)) import Data.Default (Default(..))
@ -126,7 +127,7 @@ blockToDokuWiki opts (Plain inlines) =
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
-- dokuwiki doesn't support captions - so combine together alt and caption into alt -- dokuwiki doesn't support captions - so combine together alt and caption into alt
blockToDokuWiki opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do blockToDokuWiki opts (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
capt <- if null txt capt <- if null txt
then return "" then return ""
else (" " ++) `fmap` inlineListToDokuWiki opts txt else (" " ++) `fmap` inlineListToDokuWiki opts txt
@ -135,7 +136,7 @@ blockToDokuWiki opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
else "|" ++ if null tit then capt else tit ++ capt else "|" ++ if null tit then capt else tit ++ capt
-- Relative links fail isURI and receive a colon -- Relative links fail isURI and receive a colon
prefix = if isURI src then "" else ":" prefix = if isURI src then "" else ":"
return $ "{{" ++ prefix ++ src ++ opt ++ "}}\n" return $ "{{" ++ prefix ++ src ++ imageDims opts attr ++ opt ++ "}}\n"
blockToDokuWiki opts (Para inlines) = do blockToDokuWiki opts (Para inlines) = do
indent <- stIndent <$> ask indent <- stIndent <$> ask
@ -462,7 +463,7 @@ inlineToDokuWiki _ (LineBreak) = return "\\\\\n"
inlineToDokuWiki _ Space = return " " inlineToDokuWiki _ Space = return " "
inlineToDokuWiki opts (Link txt (src, _)) = do inlineToDokuWiki opts (Link _ txt (src, _)) = do
label <- inlineListToDokuWiki opts txt label <- inlineListToDokuWiki opts txt
case txt of case txt of
[Str s] | "mailto:" `isPrefixOf` src -> return $ "<" ++ s ++ ">" [Str s] | "mailto:" `isPrefixOf` src -> return $ "<" ++ s ++ ">"
@ -473,7 +474,7 @@ inlineToDokuWiki opts (Link txt (src, _)) = do
where src' = case src of where src' = case src of
'/':xs -> xs -- with leading / it's a '/':xs -> xs -- with leading / it's a
_ -> src -- link to a help page _ -> src -- link to a help page
inlineToDokuWiki opts (Image alt (source, tit)) = do inlineToDokuWiki opts (Image attr alt (source, tit)) = do
alt' <- inlineListToDokuWiki opts alt alt' <- inlineListToDokuWiki opts alt
let txt = case (tit, alt) of let txt = case (tit, alt) of
("", []) -> "" ("", []) -> ""
@ -481,10 +482,21 @@ inlineToDokuWiki opts (Image alt (source, tit)) = do
(_ , _ ) -> "|" ++ tit (_ , _ ) -> "|" ++ tit
-- Relative links fail isURI and receive a colon -- Relative links fail isURI and receive a colon
prefix = if isURI source then "" else ":" prefix = if isURI source then "" else ":"
return $ "{{" ++ prefix ++ source ++ txt ++ "}}" return $ "{{" ++ prefix ++ source ++ imageDims opts attr ++ txt ++ "}}"
inlineToDokuWiki opts (Note contents) = do inlineToDokuWiki opts (Note contents) = do
contents' <- blockListToDokuWiki opts contents contents' <- blockListToDokuWiki opts contents
modify (\s -> s { stNotes = True }) modify (\s -> s { stNotes = True })
return $ "((" ++ contents' ++ "))" return $ "((" ++ contents' ++ "))"
-- note - may not work for notes with multiple blocks -- note - may not work for notes with multiple blocks
imageDims :: WriterOptions -> Attr -> String
imageDims opts attr = go (toPx $ dimension Width attr) (toPx $ dimension Height attr)
where
toPx = fmap (showInPixel opts) . checkPct
checkPct (Just (Percent _)) = Nothing
checkPct maybeDim = maybeDim
go (Just w) Nothing = "?" ++ w
go (Just w) (Just h) = "?" ++ w ++ "x" ++ h
go Nothing (Just h) = "?0x" ++ h
go Nothing Nothing = ""

View file

@ -455,10 +455,10 @@ writeEPUB opts doc@(Pandoc meta _) = do
chapters' [1..] chapters' [1..]
let fixInternalReferences :: Inline -> Inline let fixInternalReferences :: Inline -> Inline
fixInternalReferences (Link lab ('#':xs, tit)) = fixInternalReferences (Link attr lab ('#':xs, tit)) =
case lookup xs reftable of case lookup xs reftable of
Just ys -> Link lab (ys, tit) Just ys -> Link attr lab (ys, tit)
Nothing -> Link lab ('#':xs, tit) Nothing -> Link attr lab ('#':xs, tit)
fixInternalReferences x = x fixInternalReferences x = x
-- internal reference IDs change when we chunk the file, -- internal reference IDs change when we chunk the file,
@ -870,14 +870,14 @@ transformInline :: WriterOptions
-> IORef [(FilePath, (FilePath, Maybe Entry))] -- ^ (oldpath, newpath) media -> IORef [(FilePath, (FilePath, Maybe Entry))] -- ^ (oldpath, newpath) media
-> Inline -> Inline
-> IO Inline -> IO Inline
transformInline opts mediaRef (Image lab (src,tit)) = do transformInline opts mediaRef (Image attr lab (src,tit)) = do
newsrc <- modifyMediaRef opts mediaRef src newsrc <- modifyMediaRef opts mediaRef src
return $ Image lab (newsrc, tit) return $ Image attr lab (newsrc, tit)
transformInline opts mediaRef (x@(Math t m)) transformInline opts mediaRef (x@(Math t m))
| WebTeX url <- writerHTMLMathMethod opts = do | WebTeX url <- writerHTMLMathMethod opts = do
newsrc <- modifyMediaRef opts mediaRef (url ++ urlEncode m) newsrc <- modifyMediaRef opts mediaRef (url ++ urlEncode m)
let mathclass = if t == DisplayMath then "display" else "inline" let mathclass = if t == DisplayMath then "display" else "inline"
return $ Span ("",["math",mathclass],[]) [Image [x] (newsrc, "")] return $ Span ("",["math",mathclass],[]) [Image nullAttr [x] (newsrc, "")]
transformInline opts mediaRef (RawInline fmt raw) transformInline opts mediaRef (RawInline fmt raw)
| fmt == Format "html" = do | fmt == Format "html" = do
let tags = parseTags raw let tags = parseTags raw

View file

@ -314,8 +314,8 @@ blockToXml :: Block -> FBM [Content]
blockToXml (Plain ss) = cMapM toXml ss -- FIXME: can lead to malformed FB2 blockToXml (Plain ss) = cMapM toXml ss -- FIXME: can lead to malformed FB2
blockToXml (Para [Math DisplayMath formula]) = insertMath NormalImage formula blockToXml (Para [Math DisplayMath formula]) = insertMath NormalImage formula
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
blockToXml (Para [Image alt (src,'f':'i':'g':':':tit)]) = blockToXml (Para [Image atr alt (src,'f':'i':'g':':':tit)]) =
insertImage NormalImage (Image alt (src,tit)) insertImage NormalImage (Image atr alt (src,tit))
blockToXml (Para ss) = liftM (list . el "p") $ cMapM toXml ss blockToXml (Para ss) = liftM (list . el "p") $ cMapM toXml ss
blockToXml (CodeBlock _ s) = return . spaceBeforeAfter . blockToXml (CodeBlock _ s) = return . spaceBeforeAfter .
map (el "p" . el "code") . lines $ s map (el "p" . el "code") . lines $ s
@ -442,7 +442,7 @@ toXml Space = return [txt " "]
toXml LineBreak = return [el "empty-line" ()] toXml LineBreak = return [el "empty-line" ()]
toXml (Math _ formula) = insertMath InlineImage formula toXml (Math _ formula) = insertMath InlineImage formula
toXml (RawInline _ _) = return [] -- raw TeX and raw HTML are suppressed toXml (RawInline _ _) = return [] -- raw TeX and raw HTML are suppressed
toXml (Link text (url,ttl)) = do toXml (Link _ text (url,ttl)) = do
fns <- footnotes `liftM` get fns <- footnotes `liftM` get
let n = 1 + length fns let n = 1 + length fns
let ln_id = linkID n let ln_id = linkID n
@ -459,7 +459,7 @@ toXml (Link text (url,ttl)) = do
( [ attr ("l","href") ('#':ln_id) ( [ attr ("l","href") ('#':ln_id)
, uattr "type" "note" ] , uattr "type" "note" ]
, ln_ref) ] , ln_ref) ]
toXml img@(Image _ _) = insertImage InlineImage img toXml img@(Image _ _ _) = insertImage InlineImage img
toXml (Note bs) = do toXml (Note bs) = do
fns <- footnotes `liftM` get fns <- footnotes `liftM` get
let n = 1 + length fns let n = 1 + length fns
@ -478,12 +478,12 @@ insertMath immode formula = do
WebTeX url -> do WebTeX url -> do
let alt = [Code nullAttr formula] let alt = [Code nullAttr formula]
let imgurl = url ++ urlEncode formula let imgurl = url ++ urlEncode formula
let img = Image alt (imgurl, "") let img = Image nullAttr alt (imgurl, "")
insertImage immode img insertImage immode img
_ -> return [el "code" formula] _ -> return [el "code" formula]
insertImage :: ImageMode -> Inline -> FBM [Content] insertImage :: ImageMode -> Inline -> FBM [Content]
insertImage immode (Image alt (url,ttl)) = do insertImage immode (Image _ alt (url,ttl)) = do
images <- imagesToFetch `liftM` get images <- imagesToFetch `liftM` get
let n = 1 + length images let n = 1 + length images
let fname = "image" ++ show n let fname = "image" ++ show n
@ -572,8 +572,8 @@ plain Space = " "
plain LineBreak = "\n" plain LineBreak = "\n"
plain (Math _ s) = s plain (Math _ s) = s
plain (RawInline _ s) = s plain (RawInline _ s) = s
plain (Link text (url,_)) = concat (map plain text ++ [" <", url, ">"]) plain (Link _ text (url,_)) = concat (map plain text ++ [" <", url, ">"])
plain (Image alt _) = concat (map plain alt) plain (Image _ alt _) = concat (map plain alt)
plain (Note _) = "" -- FIXME plain (Note _) = "" -- FIXME
-- | Create an XML element. -- | Create an XML element.

View file

@ -35,6 +35,7 @@ import Text.Pandoc.Compat.Monoid ((<>))
import Text.Pandoc.Shared import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared import Text.Pandoc.Writers.Shared
import Text.Pandoc.Options import Text.Pandoc.Options
import Text.Pandoc.ImageSize
import Text.Pandoc.Templates import Text.Pandoc.Templates
import Text.Pandoc.Readers.TeXMath import Text.Pandoc.Readers.TeXMath
import Text.Pandoc.Slides import Text.Pandoc.Slides
@ -356,10 +357,10 @@ parseMailto s = do
_ -> fail "not a mailto: URL" _ -> fail "not a mailto: URL"
-- | Obfuscate a "mailto:" link. -- | Obfuscate a "mailto:" link.
obfuscateLink :: WriterOptions -> Html -> String -> Html obfuscateLink :: WriterOptions -> Attr -> Html -> String -> Html
obfuscateLink opts txt s | writerEmailObfuscation opts == NoObfuscation = obfuscateLink opts attr txt s | writerEmailObfuscation opts == NoObfuscation =
H.a ! A.href (toValue s) $ txt addAttrs opts attr $ H.a ! A.href (toValue s) $ txt
obfuscateLink opts (renderHtml -> txt) s = obfuscateLink opts attr (renderHtml -> txt) s =
let meth = writerEmailObfuscation opts let meth = writerEmailObfuscation opts
s' = map toLower (take 7 s) ++ drop 7 s s' = map toLower (take 7 s) ++ drop 7 s
in case parseMailto s' of in case parseMailto s' of
@ -385,7 +386,7 @@ obfuscateLink opts (renderHtml -> txt) s =
linkText ++ "+'<\\/'+'a'+'>');\n// -->\n")) >> linkText ++ "+'<\\/'+'a'+'>');\n// -->\n")) >>
H.noscript (preEscapedString $ obfuscateString altText) H.noscript (preEscapedString $ obfuscateString altText)
_ -> error $ "Unknown obfuscation method: " ++ show meth _ -> error $ "Unknown obfuscation method: " ++ show meth
_ -> H.a ! A.href (toValue s) $ toHtml txt -- malformed email _ -> addAttrs opts attr $ H.a ! A.href (toValue s) $ toHtml txt -- malformed email
-- | Obfuscate character as entity. -- | Obfuscate character as entity.
obfuscateChar :: Char -> String obfuscateChar :: Char -> String
@ -401,11 +402,33 @@ obfuscateString = concatMap obfuscateChar . fromEntities
addAttrs :: WriterOptions -> Attr -> Html -> Html addAttrs :: WriterOptions -> Attr -> Html -> Html
addAttrs opts attr h = foldl (!) h (attrsToHtml opts attr) addAttrs opts attr h = foldl (!) h (attrsToHtml opts attr)
toAttrs :: [(String, String)] -> [Attribute]
toAttrs kvs = map (\(x,y) -> customAttribute (fromString x) (toValue y)) kvs
attrsToHtml :: WriterOptions -> Attr -> [Attribute] attrsToHtml :: WriterOptions -> Attr -> [Attribute]
attrsToHtml opts (id',classes',keyvals) = attrsToHtml opts (id',classes',keyvals) =
[prefixedId opts id' | not (null id')] ++ [prefixedId opts id' | not (null id')] ++
[A.class_ (toValue $ unwords classes') | not (null classes')] ++ [A.class_ (toValue $ unwords classes') | not (null classes')] ++ toAttrs keyvals
map (\(x,y) -> customAttribute (fromString x) (toValue y)) keyvals
imgAttrsToHtml :: WriterOptions -> Attr -> [Attribute]
imgAttrsToHtml opts attr =
attrsToHtml opts (ident,cls,kvs') ++
toAttrs (dimensionsToAttrList opts attr)
where
(ident,cls,kvs) = attr
kvs' = filter isNotDim kvs
isNotDim ("width", _) = False
isNotDim ("height", _) = False
isNotDim _ = True
dimensionsToAttrList :: WriterOptions -> Attr -> [(String, String)]
dimensionsToAttrList opts attr = (go Width) ++ (go Height)
where
go dir = case (dimension dir attr) of
(Just (Percent a)) -> [("style", show dir ++ ":" ++ show (Percent a))]
(Just dim) -> [(show dir, showInPixel opts dim)]
_ -> []
imageExts :: [String] imageExts :: [String]
imageExts = [ "art", "bmp", "cdr", "cdt", "cpt", "cr2", "crw", "djvu", "erf", imageExts = [ "art", "bmp", "cdr", "cdt", "cpt", "cr2", "crw", "djvu", "erf",
@ -426,8 +449,8 @@ blockToHtml :: WriterOptions -> Block -> State WriterState Html
blockToHtml _ Null = return mempty blockToHtml _ Null = return mempty
blockToHtml opts (Plain lst) = inlineListToHtml opts lst blockToHtml opts (Plain lst) = inlineListToHtml opts lst
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
blockToHtml opts (Para [Image txt (s,'f':'i':'g':':':tit)]) = do blockToHtml opts (Para [Image attr txt (s,'f':'i':'g':':':tit)]) = do
img <- inlineToHtml opts (Image txt (s,tit)) img <- inlineToHtml opts (Image attr txt (s,tit))
let tocapt = if writerHtml5 opts let tocapt = if writerHtml5 opts
then H5.figcaption then H5.figcaption
else H.p ! A.class_ "caption" else H.p ! A.class_ "caption"
@ -792,10 +815,10 @@ inlineToHtml opts inline =
_ -> return mempty _ -> return mempty
| f == Format "html" -> return $ preEscapedString str | f == Format "html" -> return $ preEscapedString str
| otherwise -> return mempty | otherwise -> return mempty
(Link txt (s,_)) | "mailto:" `isPrefixOf` s -> do (Link attr txt (s,_)) | "mailto:" `isPrefixOf` s -> do
linkText <- inlineListToHtml opts txt linkText <- inlineListToHtml opts txt
return $ obfuscateLink opts linkText s return $ obfuscateLink opts attr linkText s
(Link txt (s,tit)) -> do (Link attr txt (s,tit)) -> do
linkText <- inlineListToHtml opts txt linkText <- inlineListToHtml opts txt
let s' = case s of let s' = case s of
'#':xs | writerSlideVariant opts == '#':xs | writerSlideVariant opts ==
@ -805,19 +828,23 @@ inlineToHtml opts inline =
let link' = if txt == [Str (unEscapeString s)] let link' = if txt == [Str (unEscapeString s)]
then link ! A.class_ "uri" then link ! A.class_ "uri"
else link else link
let link'' = addAttrs opts attr link'
return $ if null tit return $ if null tit
then link' then link''
else link' ! A.title (toValue tit) else link'' ! A.title (toValue tit)
(Image txt (s,tit)) | treatAsImage s -> do (Image attr txt (s,tit)) | treatAsImage s -> do
let alternate' = stringify txt
let attributes = [A.src $ toValue s] ++ let attributes = [A.src $ toValue s] ++
[A.title $ toValue tit | not $ null tit] ++ [A.title $ toValue tit | not (null tit)] ++
[A.alt $ toValue $ stringify txt] [A.alt $ toValue alternate' | not (null txt)] ++
imgAttrsToHtml opts attr
let tag = if writerHtml5 opts then H5.img else H.img let tag = if writerHtml5 opts then H5.img else H.img
return $ foldl (!) tag attributes return $ foldl (!) tag attributes
-- note: null title included, as in Markdown.pl -- note: null title included, as in Markdown.pl
(Image _ (s,tit)) -> do (Image attr _ (s,tit)) -> do
let attributes = [A.src $ toValue s] ++ let attributes = [A.src $ toValue s] ++
[A.title $ toValue tit | not $ null tit] [A.title $ toValue tit | not (null tit)] ++
imgAttrsToHtml opts attr
return $ foldl (!) H5.embed attributes return $ foldl (!) H5.embed attributes
-- note: null title included, as in Markdown.pl -- note: null title included, as in Markdown.pl
(Note contents) (Note contents)
@ -855,7 +882,7 @@ blockListToNote :: WriterOptions -> String -> [Block] -> State WriterState Html
blockListToNote opts ref blocks = blockListToNote opts ref blocks =
-- If last block is Para or Plain, include the backlink at the end of -- If last block is Para or Plain, include the backlink at the end of
-- that block. Otherwise, insert a new Plain block with the backlink. -- that block. Otherwise, insert a new Plain block with the backlink.
let backlink = [Link [Str ""] ("#" ++ writerIdentifierPrefix opts ++ "fnref" ++ ref,[])] let backlink = [Link nullAttr [Str ""] ("#" ++ writerIdentifierPrefix opts ++ "fnref" ++ ref,[])]
blocks' = if null blocks blocks' = if null blocks
then [] then []
else let lastBlock = last blocks else let lastBlock = last blocks

View file

@ -103,8 +103,8 @@ blockToHaddock opts (Plain inlines) = do
contents <- inlineListToHaddock opts inlines contents <- inlineListToHaddock opts inlines
return $ contents <> cr return $ contents <> cr
-- title beginning with fig: indicates figure -- title beginning with fig: indicates figure
blockToHaddock opts (Para [Image alt (src,'f':'i':'g':':':tit)]) = blockToHaddock opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) =
blockToHaddock opts (Para [Image alt (src,tit)]) blockToHaddock opts (Para [Image attr alt (src,tit)])
blockToHaddock opts (Para inlines) = blockToHaddock opts (Para inlines) =
-- TODO: if it contains linebreaks, we need to use a @...@ block -- TODO: if it contains linebreaks, we need to use a @...@ block
(<> blankline) `fmap` blockToHaddock opts (Plain inlines) (<> blankline) `fmap` blockToHaddock opts (Plain inlines)
@ -327,7 +327,7 @@ inlineToHaddock _ (RawInline f str)
inlineToHaddock _ (LineBreak) = return cr inlineToHaddock _ (LineBreak) = return cr
inlineToHaddock _ Space = return space inlineToHaddock _ Space = return space
inlineToHaddock opts (Cite _ lst) = inlineListToHaddock opts lst inlineToHaddock opts (Cite _ lst) = inlineListToHaddock opts lst
inlineToHaddock _opts (Link txt (src, _)) = do inlineToHaddock _ (Link _ txt (src, _)) = do
let linktext = text $ escapeString $ stringify txt let linktext = text $ escapeString $ stringify txt
let useAuto = isURI src && let useAuto = isURI src &&
case txt of case txt of
@ -335,8 +335,8 @@ inlineToHaddock _opts (Link txt (src, _)) = do
_ -> False _ -> False
return $ nowrap $ "<" <> text src <> return $ nowrap $ "<" <> text src <>
(if useAuto then empty else space <> linktext) <> ">" (if useAuto then empty else space <> linktext) <> ">"
inlineToHaddock opts (Image alternate (source, tit)) = do inlineToHaddock opts (Image attr alternate (source, tit)) = do
linkhaddock <- inlineToHaddock opts (Link alternate (source, tit)) linkhaddock <- inlineToHaddock opts (Link attr alternate (source, tit))
return $ "<" <> linkhaddock <> ">" return $ "<" <> linkhaddock <> ">"
-- haddock doesn't have notes, but we can fake it: -- haddock doesn't have notes, but we can fake it:
inlineToHaddock opts (Note contents) = do inlineToHaddock opts (Note contents) = do

View file

@ -18,14 +18,16 @@ import Text.Pandoc.Definition
import Text.Pandoc.XML import Text.Pandoc.XML
import Text.Pandoc.Readers.TeXMath (texMathToInlines) import Text.Pandoc.Readers.TeXMath (texMathToInlines)
import Text.Pandoc.Writers.Shared import Text.Pandoc.Writers.Shared
import Text.Pandoc.Shared (splitBy) import Text.Pandoc.Shared (splitBy, fetchItem, warn)
import Text.Pandoc.Options import Text.Pandoc.Options
import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Pretty import Text.Pandoc.Pretty
import Text.Pandoc.ImageSize
import Data.List (isPrefixOf, isInfixOf, stripPrefix) import Data.List (isPrefixOf, isInfixOf, stripPrefix)
import Data.Text as Text (breakOnAll, pack) import Data.Text as Text (breakOnAll, pack)
import Control.Monad.State import Control.Monad.State
import Network.URI (isURI) import Network.URI (isURI)
import System.FilePath (pathSeparator)
import qualified Data.Set as Set import qualified Data.Set as Set
type Style = [String] type Style = [String]
@ -39,7 +41,7 @@ data WriterState = WriterState{
, maxListDepth :: Int , maxListDepth :: Int
} }
type WS a = State WriterState a type WS a = StateT WriterState IO a
defaultWriterState :: WriterState defaultWriterState :: WriterState
defaultWriterState = WriterState{ defaultWriterState = WriterState{
@ -91,6 +93,7 @@ lowerAlphaName :: String
upperAlphaName :: String upperAlphaName :: String
subListParName :: String subListParName :: String
footnoteName :: String footnoteName :: String
citeName :: String
paragraphName = "Paragraph" paragraphName = "Paragraph"
codeBlockName = "CodeBlock" codeBlockName = "CodeBlock"
blockQuoteName = "Blockquote" blockQuoteName = "Blockquote"
@ -113,28 +116,29 @@ lowerAlphaName = "lowerAlpha"
upperAlphaName = "upperAlpha" upperAlphaName = "upperAlpha"
subListParName = "subParagraph" subListParName = "subParagraph"
footnoteName = "Footnote" footnoteName = "Footnote"
citeName = "Cite"
-- | Convert Pandoc document to string in ICML format. -- | Convert Pandoc document to string in ICML format.
writeICML :: WriterOptions -> Pandoc -> String writeICML :: WriterOptions -> Pandoc -> IO String
writeICML opts (Pandoc meta blocks) = writeICML opts (Pandoc meta blocks) = do
let colwidth = if writerWrapText opts let colwidth = if writerWrapText opts
then Just $ writerColumns opts then Just $ writerColumns opts
else Nothing else Nothing
render' = render colwidth render' = render colwidth
renderMeta f s = Just $ render' $ fst $ runState (f opts [] s) defaultWriterState renderMeta f s = liftM (render' . fst) $ runStateT (f opts [] s) defaultWriterState
Just metadata = metaToJSON opts metadata <- metaToJSON opts
(renderMeta blocksToICML) (renderMeta blocksToICML)
(renderMeta inlinesToICML) (renderMeta inlinesToICML)
meta meta
(doc, st) = runState (blocksToICML opts [] blocks) defaultWriterState (doc, st) <- runStateT (blocksToICML opts [] blocks) defaultWriterState
main = render' doc let main = render' doc
context = defField "body" main context = defField "body" main
$ defField "charStyles" (render' $ charStylesToDoc st) $ defField "charStyles" (render' $ charStylesToDoc st)
$ defField "parStyles" (render' $ parStylesToDoc st) $ defField "parStyles" (render' $ parStylesToDoc st)
$ defField "hyperlinks" (render' $ hyperlinksToDoc $ links st) $ defField "hyperlinks" (render' $ hyperlinksToDoc $ links st)
$ metadata $ metadata
in if writerStandalone opts return $ if writerStandalone opts
then renderTemplate' (writerTemplate opts) context then renderTemplate' (writerTemplate opts) context
else main else main
@ -407,7 +411,7 @@ inlineToICML opts style (Subscript lst) = inlinesToICML opts (subscriptName:styl
inlineToICML opts style (SmallCaps lst) = inlinesToICML opts (smallCapsName:style) lst inlineToICML opts style (SmallCaps lst) = inlinesToICML opts (smallCapsName:style) lst
inlineToICML opts style (Quoted SingleQuote lst) = inlinesToICML opts style $ [Str ""] ++ lst ++ [Str ""] inlineToICML opts style (Quoted SingleQuote lst) = inlinesToICML opts style $ [Str ""] ++ lst ++ [Str ""]
inlineToICML opts style (Quoted DoubleQuote lst) = inlinesToICML opts style $ [Str ""] ++ lst ++ [Str ""] inlineToICML opts style (Quoted DoubleQuote lst) = inlinesToICML opts style $ [Str ""] ++ lst ++ [Str ""]
inlineToICML opts style (Cite _ lst) = inlinesToICML opts style lst inlineToICML opts style (Cite _ lst) = inlinesToICML opts (citeName:style) lst
inlineToICML _ style (Code _ str) = charStyle (codeName:style) $ text $ escapeStringForXML str inlineToICML _ style (Code _ str) = charStyle (codeName:style) $ text $ escapeStringForXML str
inlineToICML _ style Space = charStyle style space inlineToICML _ style Space = charStyle style space
inlineToICML _ style LineBreak = charStyle style $ text lineSeparator inlineToICML _ style LineBreak = charStyle style $ text lineSeparator
@ -416,7 +420,7 @@ inlineToICML opts style (Math mt str) =
inlineToICML _ _ (RawInline f str) inlineToICML _ _ (RawInline f str)
| f == Format "icml" = return $ text str | f == Format "icml" = return $ text str
| otherwise = return empty | otherwise = return empty
inlineToICML opts style (Link lst (url, title)) = do inlineToICML opts style (Link _ lst (url, title)) = do
content <- inlinesToICML opts (linkName:style) lst content <- inlinesToICML opts (linkName:style) lst
state $ \st -> state $ \st ->
let ident = if null $ links st let ident = if null $ links st
@ -426,7 +430,7 @@ inlineToICML opts style (Link lst (url, title)) = do
cont = inTags True "HyperlinkTextSource" cont = inTags True "HyperlinkTextSource"
[("Self","htss-"++show ident), ("Name",title), ("Hidden","false")] content [("Self","htss-"++show ident), ("Name",title), ("Hidden","false")] content
in (cont, newst) in (cont, newst)
inlineToICML opts style (Image alt target) = imageICML opts style alt target inlineToICML opts style (Image attr alt target) = imageICML opts style attr alt target
inlineToICML opts style (Note lst) = footnoteToICML opts style lst inlineToICML opts style (Note lst) = footnoteToICML opts style lst
inlineToICML opts style (Span _ lst) = inlinesToICML opts style lst inlineToICML opts style (Span _ lst) = inlinesToICML opts style lst
@ -499,39 +503,48 @@ styleToStrAttr style =
in (stlStr, attrs) in (stlStr, attrs)
-- | Assemble an ICML Image. -- | Assemble an ICML Image.
imageICML :: WriterOptions -> Style -> [Inline] -> Target -> WS Doc imageICML :: WriterOptions -> Style -> Attr -> [Inline] -> Target -> WS Doc
imageICML _ style _ (linkURI, _) = imageICML opts style attr _ (src, _) = do
let imgWidth = 300::Int --TODO: set width, height dynamically as in Docx.hs res <- liftIO $ fetchItem (writerSourceURL opts) src
imgHeight = 200::Int imgS <- case res of
scaleFact = show (1::Double) --TODO: set scaling factor so image is scaled exactly to imgWidth x imgHeight Left (_) -> do
hw = show $ imgWidth `div` 2 liftIO $ warn $ "Could not find image `" ++ src ++ "', skipping..."
hh = show $ imgHeight `div` 2 return def
qw = show $ imgWidth `div` 4 Right (img, _) -> do
qh = show $ imgHeight `div` 4 case imageSize img of
uriPrefix = if isURI linkURI then "" else "file:" Right size -> return size
Left msg -> do
return $ warn $ "Could not determine image size in `" ++
src ++ "': " ++ msg
return def
let (ow, oh) = sizeInPoints imgS
(imgWidth, imgHeight) = desiredSizeInPoints opts attr imgS
hw = showFl $ ow / 2
hh = showFl $ oh / 2
scale = showFl (imgWidth / ow) ++ " 0 0 " ++ showFl (imgHeight / oh)
src' = if isURI src then src else "file://." ++ pathSeparator : src
(stlStr, attrs) = styleToStrAttr style (stlStr, attrs) = styleToStrAttr style
props = inTags True "Properties" [] $ inTags True "PathGeometry" [] props = inTags True "Properties" [] $ inTags True "PathGeometry" []
$ inTags True "GeometryPathType" [("PathOpen","false")] $ inTags True "GeometryPathType" [("PathOpen","false")]
$ inTags True "PathPointArray" [] $ inTags True "PathPointArray" []
$ vcat [ $ vcat [
selfClosingTag "PathPointType" [("Anchor", "-"++qw++" -"++qh), selfClosingTag "PathPointType" [("Anchor", "-"++hw++" -"++hh),
("LeftDirection", "-"++qw++" -"++qh), ("RightDirection", "-"++qw++" -"++qh)] ("LeftDirection", "-"++hw++" -"++hh), ("RightDirection", "-"++hw++" -"++hh)]
, selfClosingTag "PathPointType" [("Anchor", "-"++qw++" "++qh), , selfClosingTag "PathPointType" [("Anchor", "-"++hw++" "++hh),
("LeftDirection", "-"++qw++" "++qh), ("RightDirection", "-"++qw++" "++qh)] ("LeftDirection", "-"++hw++" "++hh), ("RightDirection", "-"++hw++" "++hh)]
, selfClosingTag "PathPointType" [("Anchor", qw++" "++qh), , selfClosingTag "PathPointType" [("Anchor", hw++" "++hh),
("LeftDirection", qw++" "++qh), ("RightDirection", qw++" "++qh)] ("LeftDirection", hw++" "++hh), ("RightDirection", hw++" "++hh)]
, selfClosingTag "PathPointType" [("Anchor", qw++" -"++qh), , selfClosingTag "PathPointType" [("Anchor", hw++" -"++hh),
("LeftDirection", qw++" -"++qh), ("RightDirection", qw++" -"++qh)] ("LeftDirection", hw++" -"++hh), ("RightDirection", hw++" -"++hh)]
] ]
image = inTags True "Image" image = inTags True "Image"
[("Self","ue6"), ("ItemTransform", scaleFact++" 0 0 "++scaleFact++" -"++qw++" -"++qh)] [("Self","ue6"), ("ItemTransform", scale++" -"++hw++" -"++hh)]
$ vcat [ $ vcat [
inTags True "Properties" [] $ inTags True "Profile" [("type","string")] $ text "$ID/Embedded" inTags True "Properties" [] $ inTags True "Profile" [("type","string")] $ text "$ID/Embedded"
$$ selfClosingTag "GraphicBounds" [("Left","0"), ("Top","0"), ("Right", hw), ("Bottom", hh)] , selfClosingTag "Link" [("Self", "ueb"), ("LinkResourceURI", src')]
, selfClosingTag "Link" [("Self", "ueb"), ("LinkResourceURI", uriPrefix++linkURI)]
] ]
doc = inTags True "CharacterStyleRange" attrs doc = inTags True "CharacterStyleRange" attrs
$ inTags True "Rectangle" [("Self","uec"), ("ItemTransform", "1 0 0 1 "++qw++" -"++qh)] $ inTags True "Rectangle" [("Self","uec"), ("StrokeWeight", "0"),
("ItemTransform", scale++" "++hw++" -"++hh)]
$ (props $$ image) $ (props $$ image)
in do
state $ \st -> (doc, st{ inlineStyles = Set.insert stlStr $ inlineStyles st } ) state $ \st -> (doc, st{ inlineStyles = Set.insert stlStr $ inlineStyles st } )

View file

@ -47,6 +47,7 @@ import Control.Applicative ((<|>))
import Control.Monad.State import Control.Monad.State
import qualified Text.Parsec as P import qualified Text.Parsec as P
import Text.Pandoc.Pretty import Text.Pandoc.Pretty
import Text.Pandoc.ImageSize
import Text.Pandoc.Slides import Text.Pandoc.Slides
import Text.Pandoc.Highlighting (highlight, styleToLaTeX, import Text.Pandoc.Highlighting (highlight, styleToLaTeX,
formatLaTeXInline, formatLaTeXBlock, formatLaTeXInline, formatLaTeXBlock,
@ -99,7 +100,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do
_ -> blocks _ -> blocks
else blocks else blocks
-- see if there are internal links -- see if there are internal links
let isInternalLink (Link _ ('#':xs,_)) = [xs] let isInternalLink (Link _ _ ('#':xs,_)) = [xs]
isInternalLink _ = [] isInternalLink _ = []
modify $ \s -> s{ stInternalLinks = query isInternalLink blocks' } modify $ \s -> s{ stInternalLinks = query isInternalLink blocks' }
let template = writerTemplate options let template = writerTemplate options
@ -395,7 +396,7 @@ blockToLaTeX (Div (identifier,classes,kvs) bs) = do
blockToLaTeX (Plain lst) = blockToLaTeX (Plain lst) =
inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
blockToLaTeX (Para [Image txt (src,'f':'i':'g':':':tit)]) = do blockToLaTeX (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
inNote <- gets stInNote inNote <- gets stInNote
modify $ \st -> st{ stInMinipage = True, stNotes = [] } modify $ \st -> st{ stInMinipage = True, stNotes = [] }
capt <- inlineListToLaTeX txt capt <- inlineListToLaTeX txt
@ -405,7 +406,7 @@ blockToLaTeX (Para [Image txt (src,'f':'i':'g':':':tit)]) = do
captForLof <- if null notes captForLof <- if null notes
then return empty then return empty
else brackets <$> inlineListToLaTeX (walk deNote txt) else brackets <$> inlineListToLaTeX (walk deNote txt)
img <- inlineToLaTeX (Image txt (src,tit)) img <- inlineToLaTeX (Image attr txt (src,tit))
let footnotes = notesToLaTeX notes let footnotes = notesToLaTeX notes
return $ if inNote return $ if inNote
-- can't have figures in notes -- can't have figures in notes
@ -684,12 +685,19 @@ listItemToLaTeX lst
defListItemToLaTeX :: ([Inline], [[Block]]) -> State WriterState Doc defListItemToLaTeX :: ([Inline], [[Block]]) -> State WriterState Doc
defListItemToLaTeX (term, defs) = do defListItemToLaTeX (term, defs) = do
term' <- inlineListToLaTeX term term' <- inlineListToLaTeX term
-- put braces around term if it contains an internal link,
-- since otherwise we get bad bracket interactions: \item[\hyperref[..]
let isInternalLink (Link _ _ ('#':_,_)) = True
isInternalLink _ = False
let term'' = if any isInternalLink term
then braces term'
else term'
def' <- liftM vsep $ mapM blockListToLaTeX defs def' <- liftM vsep $ mapM blockListToLaTeX defs
return $ case defs of return $ case defs of
(((Header _ _ _) : _) : _) -> (((Header _ _ _) : _) : _) ->
"\\item" <> brackets term' <> " ~ " $$ def' "\\item" <> brackets term'' <> " ~ " $$ def'
_ -> _ ->
"\\item" <> brackets term' $$ def' "\\item" <> brackets term'' $$ def'
-- | Craft the section header, inserting the secton reference, if supplied. -- | Craft the section header, inserting the secton reference, if supplied.
sectionHeader :: Bool -- True for unnumbered sectionHeader :: Bool -- True for unnumbered
@ -893,11 +901,11 @@ inlineToLaTeX (RawInline f str)
| otherwise = return empty | otherwise = return empty
inlineToLaTeX (LineBreak) = return $ "\\\\" <> cr inlineToLaTeX (LineBreak) = return $ "\\\\" <> cr
inlineToLaTeX Space = return space inlineToLaTeX Space = return space
inlineToLaTeX (Link txt ('#':ident, _)) = do inlineToLaTeX (Link _ txt ('#':ident, _)) = do
contents <- inlineListToLaTeX txt contents <- inlineListToLaTeX txt
lab <- toLabel ident lab <- toLabel ident
return $ text "\\protect\\hyperlink" <> braces (text lab) <> braces contents return $ text "\\protect\\hyperlink" <> braces (text lab) <> braces contents
inlineToLaTeX (Link txt (src, _)) = inlineToLaTeX (Link _ txt (src, _)) =
case txt of case txt of
[Str x] | escapeURI x == src -> -- autolink [Str x] | escapeURI x == src -> -- autolink
do modify $ \s -> s{ stUrl = True } do modify $ \s -> s{ stUrl = True }
@ -914,16 +922,31 @@ inlineToLaTeX (Link txt (src, _)) =
src' <- stringToLaTeX URLString (escapeURI src) src' <- stringToLaTeX URLString (escapeURI src)
return $ text ("\\href{" ++ src' ++ "}{") <> return $ text ("\\href{" ++ src' ++ "}{") <>
contents <> char '}' contents <> char '}'
inlineToLaTeX (Image _ (source, _)) = do inlineToLaTeX (Image attr _ (source, _)) = do
modify $ \s -> s{ stGraphics = True } modify $ \s -> s{ stGraphics = True }
let source' = if isURI source opts <- gets stOptions
let showDim dir = let d = text (show dir) <> "="
in case (dimension dir attr) of
Just (Pixel a) ->
[d <> text (showInInch opts (Pixel a)) <> "in"]
Just (Percent a) ->
[d <> text (showFl (a / 100)) <> "\\textwidth"]
Just dim ->
[d <> text (show dim)]
Nothing ->
[]
dimList = showDim Width ++ showDim Height
dims = if null dimList
then empty
else brackets $ cat (intersperse "," dimList)
source' = if isURI source
then source then source
else unEscapeString source else unEscapeString source
source'' <- stringToLaTeX URLString (escapeURI source') source'' <- stringToLaTeX URLString (escapeURI source')
inHeading <- gets stInHeading inHeading <- gets stInHeading
return $ return $
(if inHeading then "\\protect\\includegraphics" else "\\includegraphics") (if inHeading then "\\protect\\includegraphics" else "\\includegraphics") <>
<> braces (text source'') dims <> braces (text source'')
inlineToLaTeX (Note contents) = do inlineToLaTeX (Note contents) = do
inMinipage <- gets stInMinipage inMinipage <- gets stInMinipage
modify (\s -> s{stInNote = True}) modify (\s -> s{stInNote = True})

View file

@ -344,7 +344,7 @@ inlineToMan _ (RawInline f str)
inlineToMan _ (LineBreak) = return $ inlineToMan _ (LineBreak) = return $
cr <> text ".PD 0" $$ text ".P" $$ text ".PD" <> cr cr <> text ".PD 0" $$ text ".P" $$ text ".PD" <> cr
inlineToMan _ Space = return space inlineToMan _ Space = return space
inlineToMan opts (Link txt (src, _)) = do inlineToMan opts (Link _ txt (src, _)) = do
linktext <- inlineListToMan opts txt linktext <- inlineListToMan opts txt
let srcSuffix = fromMaybe src (stripPrefix "mailto:" src) let srcSuffix = fromMaybe src (stripPrefix "mailto:" src)
return $ case txt of return $ case txt of
@ -352,12 +352,12 @@ inlineToMan opts (Link txt (src, _)) = do
| escapeURI s == srcSuffix -> | escapeURI s == srcSuffix ->
char '<' <> text srcSuffix <> char '>' char '<' <> text srcSuffix <> char '>'
_ -> linktext <> text " (" <> text src <> char ')' _ -> linktext <> text " (" <> text src <> char ')'
inlineToMan opts (Image alternate (source, tit)) = do inlineToMan opts (Image attr alternate (source, tit)) = do
let txt = if (null alternate) || (alternate == [Str ""]) || let txt = if (null alternate) || (alternate == [Str ""]) ||
(alternate == [Str source]) -- to prevent autolinks (alternate == [Str source]) -- to prevent autolinks
then [Str "image"] then [Str "image"]
else alternate else alternate
linkPart <- inlineToMan opts (Link txt (source, tit)) linkPart <- inlineToMan opts (Link attr txt (source, tit))
return $ char '[' <> text "IMAGE: " <> linkPart <> char ']' return $ char '[' <> text "IMAGE: " <> linkPart <> char ']'
inlineToMan _ (Note contents) = do inlineToMan _ (Note contents) = do
-- add to notes in state -- add to notes in state

View file

@ -55,7 +55,8 @@ import qualified Data.Vector as V
import qualified Data.Text as T import qualified Data.Text as T
type Notes = [[Block]] type Notes = [[Block]]
type Refs = [([Inline], Target)] type Ref = ([Inline], Target, Attr)
type Refs = [Ref]
data WriterState = WriterState { stNotes :: Notes data WriterState = WriterState { stNotes :: Notes
, stRefs :: Refs , stRefs :: Refs
, stRefShortcutable :: Bool , stRefShortcutable :: Bool
@ -200,15 +201,16 @@ refsToMarkdown opts refs = mapM (keyToMarkdown opts) refs >>= return . vcat
-- | Return markdown representation of a reference key. -- | Return markdown representation of a reference key.
keyToMarkdown :: WriterOptions keyToMarkdown :: WriterOptions
-> ([Inline], (String, String)) -> Ref
-> State WriterState Doc -> State WriterState Doc
keyToMarkdown opts (label, (src, tit)) = do keyToMarkdown opts (label, (src, tit), attr) = do
label' <- inlineListToMarkdown opts label label' <- inlineListToMarkdown opts label
let tit' = if null tit let tit' = if null tit
then empty then empty
else space <> "\"" <> text tit <> "\"" else space <> "\"" <> text tit <> "\""
return $ nest 2 $ hang 2 return $ nest 2 $ hang 2
("[" <> label' <> "]:" <> space) (text src <> tit') ("[" <> label' <> "]:" <> space) (text src <> tit')
<> linkAttributes opts attr
-- | Return markdown representation of notes. -- | Return markdown representation of notes.
notesToMarkdown :: WriterOptions -> [[Block]] -> State WriterState Doc notesToMarkdown :: WriterOptions -> [[Block]] -> State WriterState Doc
@ -264,7 +266,7 @@ elementToListItem opts (Sec lev _nums (ident,_,_) headerText subsecs)
not (null subsecs) && lev < writerTOCDepth opts ] not (null subsecs) && lev < writerTOCDepth opts ]
where headerLink = if null ident where headerLink = if null ident
then headerText then headerText
else [Link headerText ('#':ident, "")] else [Link nullAttr headerText ('#':ident, "")]
elementToListItem _ (Blk _) = [] elementToListItem _ (Blk _) = []
attrsToMarkdown :: Attr -> Doc attrsToMarkdown :: Attr -> Doc
@ -283,6 +285,12 @@ attrsToMarkdown attribs = braces $ hsep [attribId, attribClasses, attribKeys]
map (\(k,v) -> text k map (\(k,v) -> text k
<> "=\"" <> text v <> "\"") ks <> "=\"" <> text v <> "\"") ks
linkAttributes :: WriterOptions -> Attr -> Doc
linkAttributes opts attr =
if isEnabled Ext_common_link_attributes opts && attr /= nullAttr
then attrsToMarkdown attr
else empty
-- | Ordered list start parser for use in Para below. -- | Ordered list start parser for use in Para below.
olMarker :: Parser [Char] ParserState Char olMarker :: Parser [Char] ParserState Char
olMarker = do (start, style', delim) <- anyOrderedListMarker olMarker = do (start, style', delim) <- anyOrderedListMarker
@ -328,8 +336,8 @@ blockToMarkdown opts (Plain inlines) = do
else contents else contents
return $ contents' <> cr return $ contents' <> cr
-- title beginning with fig: indicates figure -- title beginning with fig: indicates figure
blockToMarkdown opts (Para [Image alt (src,'f':'i':'g':':':tit)]) = blockToMarkdown opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) =
blockToMarkdown opts (Para [Image alt (src,tit)]) blockToMarkdown opts (Para [Image attr alt (src,tit)])
blockToMarkdown opts (Para inlines) = blockToMarkdown opts (Para inlines) =
(<> blankline) `fmap` blockToMarkdown opts (Plain inlines) (<> blankline) `fmap` blockToMarkdown opts (Plain inlines)
blockToMarkdown opts (RawBlock f str) blockToMarkdown opts (RawBlock f str)
@ -668,21 +676,21 @@ blockListToMarkdown opts blocks =
-- | Get reference for target; if none exists, create unique one and return. -- | Get reference for target; if none exists, create unique one and return.
-- Prefer label if possible; otherwise, generate a unique key. -- Prefer label if possible; otherwise, generate a unique key.
getReference :: [Inline] -> Target -> State WriterState [Inline] getReference :: Attr -> [Inline] -> Target -> State WriterState [Inline]
getReference label (src, tit) = do getReference attr label target = do
st <- get st <- get
case find ((== (src, tit)) . snd) (stRefs st) of case find (\(_,t,a) -> t == target && a == attr) (stRefs st) of
Just (ref, _) -> return ref Just (ref, _, _) -> return ref
Nothing -> do Nothing -> do
let label' = case find ((== label) . fst) (stRefs st) of let label' = case find (\(l,_,_) -> l == label) (stRefs st) of
Just _ -> -- label is used; generate numerical label Just _ -> -- label is used; generate numerical label
case find (\n -> notElem [Str (show n)] case find (\n -> notElem [Str (show n)]
(map fst (stRefs st))) (map (\(l,_,_) -> l) (stRefs st)))
[1..(10000 :: Integer)] of [1..(10000 :: Integer)] of
Just x -> [Str (show x)] Just x -> [Str (show x)]
Nothing -> error "no unique label" Nothing -> error "no unique label"
Nothing -> label Nothing -> label
modify (\s -> s{ stRefs = (label', (src,tit)) : stRefs st }) modify (\s -> s{ stRefs = (label', target, attr) : stRefs st })
return label' return label'
-- | Convert list of Pandoc inline elements to markdown. -- | Convert list of Pandoc inline elements to markdown.
@ -692,10 +700,10 @@ inlineListToMarkdown opts lst = do
go (if inlist then avoidBadWrapsInList lst else lst) go (if inlist then avoidBadWrapsInList lst else lst)
where go [] = return empty where go [] = return empty
go (i:is) = case i of go (i:is) = case i of
(Link _ _) -> case is of (Link _ _ _) -> case is of
-- If a link is followed by another link or '[' we don't shortcut -- If a link is followed by another link or '[' we don't shortcut
(Link _ _):_ -> unshortcutable (Link _ _ _):_ -> unshortcutable
Space:(Link _ _):_ -> unshortcutable Space:(Link _ _ _):_ -> unshortcutable
Space:(Str('[':_)):_ -> unshortcutable Space:(Str('[':_)):_ -> unshortcutable
Space:(RawInline _ ('[':_)):_ -> unshortcutable Space:(RawInline _ ('[':_)):_ -> unshortcutable
Space:(Cite _ _):_ -> unshortcutable Space:(Cite _ _):_ -> unshortcutable
@ -897,7 +905,7 @@ inlineToMarkdown opts (Cite (c:cs) lst)
return $ pdoc <+> r return $ pdoc <+> r
modekey SuppressAuthor = "-" modekey SuppressAuthor = "-"
modekey _ = "" modekey _ = ""
inlineToMarkdown opts (Link txt (src, tit)) = do inlineToMarkdown opts (Link attr txt (src, tit)) = do
plain <- gets stPlain plain <- gets stPlain
linktext <- inlineListToMarkdown opts txt linktext <- inlineListToMarkdown opts txt
let linktitle = if null tit let linktitle = if null tit
@ -912,7 +920,7 @@ inlineToMarkdown opts (Link txt (src, tit)) = do
shortcutable <- gets stRefShortcutable shortcutable <- gets stRefShortcutable
let useShortcutRefLinks = shortcutable && let useShortcutRefLinks = shortcutable &&
isEnabled Ext_shortcut_reference_links opts isEnabled Ext_shortcut_reference_links opts
ref <- if useRefLinks then getReference txt (src, tit) else return [] ref <- if useRefLinks then getReference attr txt (src, tit) else return []
reftext <- inlineListToMarkdown opts ref reftext <- inlineListToMarkdown opts ref
return $ if useAuto return $ if useAuto
then if plain then if plain
@ -929,14 +937,15 @@ inlineToMarkdown opts (Link txt (src, tit)) = do
else if plain else if plain
then linktext then linktext
else "[" <> linktext <> "](" <> else "[" <> linktext <> "](" <>
text src <> linktitle <> ")" text src <> linktitle <> ")" <>
inlineToMarkdown opts (Image alternate (source, tit)) = do linkAttributes opts attr
inlineToMarkdown opts (Image attr alternate (source, tit)) = do
plain <- gets stPlain plain <- gets stPlain
let txt = if null alternate || alternate == [Str source] let txt = if null alternate || alternate == [Str source]
-- to prevent autolinks -- to prevent autolinks
then [Str ""] then [Str ""]
else alternate else alternate
linkPart <- inlineToMarkdown opts (Link txt (source, tit)) linkPart <- inlineToMarkdown opts (Link attr txt (source, tit))
return $ if plain return $ if plain
then "[" <> linkPart <> "]" then "[" <> linkPart <> "]"
else "!" <> linkPart else "!" <> linkPart

View file

@ -35,6 +35,7 @@ import Text.Pandoc.Options
import Text.Pandoc.Shared import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared import Text.Pandoc.Writers.Shared
import Text.Pandoc.Pretty (render) import Text.Pandoc.Pretty (render)
import Text.Pandoc.ImageSize
import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.XML ( escapeStringForXML ) import Text.Pandoc.XML ( escapeStringForXML )
import Data.List ( intersect, intercalate ) import Data.List ( intersect, intercalate )
@ -44,6 +45,7 @@ import Control.Monad.State
data WriterState = WriterState { data WriterState = WriterState {
stNotes :: Bool -- True if there are notes stNotes :: Bool -- True if there are notes
, stOptions :: WriterOptions -- writer options
} }
data WriterReader = WriterReader { data WriterReader = WriterReader {
@ -57,7 +59,7 @@ type MediaWikiWriter = ReaderT WriterReader (State WriterState)
-- | Convert Pandoc to MediaWiki. -- | Convert Pandoc to MediaWiki.
writeMediaWiki :: WriterOptions -> Pandoc -> String writeMediaWiki :: WriterOptions -> Pandoc -> String
writeMediaWiki opts document = writeMediaWiki opts document =
let initialState = WriterState { stNotes = False } let initialState = WriterState { stNotes = False, stOptions = opts }
env = WriterReader { options = opts, listLevel = [], useTags = False } env = WriterReader { options = opts, listLevel = [], useTags = False }
in evalState (runReaderT (pandocToMediaWiki document) env) initialState in evalState (runReaderT (pandocToMediaWiki document) env) initialState
@ -100,14 +102,15 @@ blockToMediaWiki (Plain inlines) =
inlineListToMediaWiki inlines inlineListToMediaWiki inlines
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
blockToMediaWiki (Para [Image txt (src,'f':'i':'g':':':tit)]) = do blockToMediaWiki (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
capt <- if null txt capt <- if null txt
then return "" then return ""
else ("|caption " ++) `fmap` inlineListToMediaWiki txt else ("|caption " ++) `fmap` inlineListToMediaWiki txt
img <- imageToMediaWiki attr
let opt = if null txt let opt = if null txt
then "" then ""
else "|alt=" ++ if null tit then capt else tit ++ capt else "|alt=" ++ if null tit then capt else tit ++ capt
return $ "[[File:" ++ src ++ "|frame|none" ++ opt ++ "]]\n" return $ "[[File:" ++ src ++ "|frame|none" ++ img ++ opt ++ "]]\n"
blockToMediaWiki (Para inlines) = do blockToMediaWiki (Para inlines) = do
tags <- asks useTags tags <- asks useTags
@ -312,6 +315,23 @@ alignmentToString alignment = case alignment of
AlignCenter -> "center" AlignCenter -> "center"
AlignDefault -> "left" AlignDefault -> "left"
imageToMediaWiki :: Attr -> MediaWikiWriter String
imageToMediaWiki attr = do
opts <- gets stOptions
let (_, cls, _) = attr
toPx = fmap (showInPixel opts) . checkPct
checkPct (Just (Percent _)) = Nothing
checkPct maybeDim = maybeDim
go (Just w) Nothing = '|':w ++ "px"
go (Just w) (Just h) = '|':w ++ "x" ++ h ++ "px"
go Nothing (Just h) = "|x" ++ h ++ "px"
go Nothing Nothing = ""
dims = go (toPx $ dimension Width attr) (toPx $ dimension Height attr)
classes = if null cls
then ""
else "|class=" ++ unwords cls
return $ dims ++ classes
-- | Convert list of Pandoc block elements to MediaWiki. -- | Convert list of Pandoc block elements to MediaWiki.
blockListToMediaWiki :: [Block] -- ^ List of block elements blockListToMediaWiki :: [Block] -- ^ List of block elements
-> MediaWikiWriter String -> MediaWikiWriter String
@ -379,7 +399,7 @@ inlineToMediaWiki (LineBreak) = return "<br />\n"
inlineToMediaWiki Space = return " " inlineToMediaWiki Space = return " "
inlineToMediaWiki (Link txt (src, _)) = do inlineToMediaWiki (Link _ txt (src, _)) = do
label <- inlineListToMediaWiki txt label <- inlineListToMediaWiki txt
case txt of case txt of
[Str s] | isURI src && escapeURI s == src -> return src [Str s] | isURI src && escapeURI s == src -> return src
@ -390,14 +410,15 @@ inlineToMediaWiki (Link txt (src, _)) = do
'/':xs -> xs -- with leading / it's a '/':xs -> xs -- with leading / it's a
_ -> src -- link to a help page _ -> src -- link to a help page
inlineToMediaWiki (Image alt (source, tit)) = do inlineToMediaWiki (Image attr alt (source, tit)) = do
img <- imageToMediaWiki attr
alt' <- inlineListToMediaWiki alt alt' <- inlineListToMediaWiki alt
let txt = if null tit let txt = if null tit
then if null alt then if null alt
then "" then ""
else '|' : alt' else '|' : alt'
else '|' : tit else '|' : tit
return $ "[[File:" ++ source ++ txt ++ "]]" return $ "[[File:" ++ source ++ img ++ txt ++ "]]"
inlineToMediaWiki (Note contents) = do inlineToMediaWiki (Note contents) = do
contents' <- blockListToMediaWiki contents contents' <- blockListToMediaWiki contents

View file

@ -40,7 +40,7 @@ import Codec.Archive.Zip
import Text.Pandoc.Options ( WriterOptions(..) ) import Text.Pandoc.Options ( WriterOptions(..) )
import Text.Pandoc.Shared ( stringify, fetchItem', warn, import Text.Pandoc.Shared ( stringify, fetchItem', warn,
getDefaultReferenceODT ) getDefaultReferenceODT )
import Text.Pandoc.ImageSize ( imageSize, sizeInPoints ) import Text.Pandoc.ImageSize ( imageSize, desiredSizeInPoints )
import Text.Pandoc.MIME ( getMimeType, extensionFromMimeType ) import Text.Pandoc.MIME ( getMimeType, extensionFromMimeType )
import Text.Pandoc.Definition import Text.Pandoc.Definition
import Text.Pandoc.Walk import Text.Pandoc.Walk
@ -126,7 +126,7 @@ writeODT opts doc@(Pandoc meta _) = do
return $ fromArchive archive'' return $ fromArchive archive''
transformPicMath :: WriterOptions -> IORef [Entry] -> Inline -> IO Inline transformPicMath :: WriterOptions -> IORef [Entry] -> Inline -> IO Inline
transformPicMath opts entriesRef (Image lab (src,t)) = do transformPicMath opts entriesRef (Image attr lab (src,t)) = do
res <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src res <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src
case res of case res of
Left (_ :: E.SomeException) -> do Left (_ :: E.SomeException) -> do
@ -134,7 +134,8 @@ transformPicMath opts entriesRef (Image lab (src,t)) = do
return $ Emph lab return $ Emph lab
Right (img, mbMimeType) -> do Right (img, mbMimeType) -> do
(w,h) <- case imageSize img of (w,h) <- case imageSize img of
Right size -> return $ sizeInPoints size Right size -> return $
desiredSizeInPoints opts attr size
Left msg -> do Left msg -> do
warn $ "Could not determine image size in `" ++ warn $ "Could not determine image size in `" ++
src ++ "': " ++ msg src ++ "': " ++ msg
@ -150,7 +151,7 @@ transformPicMath opts entriesRef (Image lab (src,t)) = do
modifyIORef entriesRef (entry:) modifyIORef entriesRef (entry:)
let fig | "fig:" `isPrefixOf` t = "fig:" let fig | "fig:" `isPrefixOf` t = "fig:"
| otherwise = "" | otherwise = ""
return $ Image lab (newsrc, fig++tit') return $ Image attr lab (newsrc, fig++tit')
transformPicMath _ entriesRef (Math t math) = do transformPicMath _ entriesRef (Math t math) = do
entries <- readIORef entriesRef entries <- readIORef entriesRef
let dt = if t == InlineMath then DisplayInline else DisplayBlock let dt = if t == InlineMath then DisplayInline else DisplayBlock

View file

@ -286,8 +286,8 @@ blockToOpenDocument o bs
| Plain b <- bs = if null b | Plain b <- bs = if null b
then return empty then return empty
else inParagraphTags =<< inlinesToOpenDocument o b else inParagraphTags =<< inlinesToOpenDocument o b
| Para [Image c (s,'f':'i':'g':':':t)] <- bs | Para [Image attr c (s,'f':'i':'g':':':t)] <- bs
= figure c s t = figure attr c s t
| Para b <- bs = if null b | Para b <- bs = if null b
then return empty then return empty
else inParagraphTags =<< inlinesToOpenDocument o b else inParagraphTags =<< inlinesToOpenDocument o b
@ -342,10 +342,10 @@ blockToOpenDocument o bs
return $ inTags True "table:table" [ ("table:name" , name) return $ inTags True "table:table" [ ("table:name" , name)
, ("table:style-name", name) , ("table:style-name", name)
] (vcat columns $$ th $$ vcat tr) $$ captionDoc ] (vcat columns $$ th $$ vcat tr) $$ captionDoc
figure caption source title | null caption = figure attr caption source title | null caption =
withParagraphStyle o "Figure" [Para [Image caption (source,title)]] withParagraphStyle o "Figure" [Para [Image attr caption (source,title)]]
| otherwise = do | otherwise = do
imageDoc <- withParagraphStyle o "FigureWithCaption" [Para [Image caption (source,title)]] imageDoc <- withParagraphStyle o "FigureWithCaption" [Para [Image attr caption (source,title)]]
captionDoc <- withParagraphStyle o "FigureCaption" [Para caption] captionDoc <- withParagraphStyle o "FigureCaption" [Para caption]
return $ imageDoc $$ captionDoc return $ imageDoc $$ captionDoc
@ -391,8 +391,8 @@ inlineToOpenDocument o ils
| RawInline f s <- ils = if f == Format "opendocument" | RawInline f s <- ils = if f == Format "opendocument"
then return $ text s then return $ text s
else return empty else return empty
| Link l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l | Link _ l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l
| Image _ (s,t) <- ils = mkImg s t | Image attr _ (s,t) <- ils = mkImg attr s t
| Note l <- ils = mkNote l | Note l <- ils = mkNote l
| otherwise = return empty | otherwise = return empty
where where
@ -401,7 +401,7 @@ inlineToOpenDocument o ils
, ("xlink:href" , s ) , ("xlink:href" , s )
, ("office:name", t ) , ("office:name", t )
] . inSpanTags "Definition" ] . inSpanTags "Definition"
mkImg s t = do mkImg _ s t = do
id' <- gets stImageId id' <- gets stImageId
modify (\st -> st{ stImageId = id' + 1 }) modify (\st -> st{ stImageId = id' + 1 })
return $ inTags False "draw:frame" return $ inTags False "draw:frame"

View file

@ -116,12 +116,12 @@ blockToOrg (Div attrs bs) = do
nest 2 endTag $$ "#+END_HTML" $$ blankline nest 2 endTag $$ "#+END_HTML" $$ blankline
blockToOrg (Plain inlines) = inlineListToOrg inlines blockToOrg (Plain inlines) = inlineListToOrg inlines
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
blockToOrg (Para [Image txt (src,'f':'i':'g':':':tit)]) = do blockToOrg (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
capt <- if null txt capt <- if null txt
then return empty then return empty
else (\c -> "#+CAPTION: " <> c <> blankline) `fmap` else (\c -> "#+CAPTION: " <> c <> blankline) `fmap`
inlineListToOrg txt inlineListToOrg txt
img <- inlineToOrg (Image txt (src,tit)) img <- inlineToOrg (Image attr txt (src,tit))
return $ capt <> img return $ capt <> img
blockToOrg (Para inlines) = do blockToOrg (Para inlines) = do
contents <- inlineListToOrg inlines contents <- inlineListToOrg inlines
@ -275,7 +275,7 @@ inlineToOrg (RawInline f str) | f == "tex" || f == "latex" = return $ text str
inlineToOrg (RawInline _ _) = return empty inlineToOrg (RawInline _ _) = return empty
inlineToOrg (LineBreak) = return (text "\\\\" <> cr) inlineToOrg (LineBreak) = return (text "\\\\" <> cr)
inlineToOrg Space = return space inlineToOrg Space = return space
inlineToOrg (Link txt (src, _)) = do inlineToOrg (Link _ txt (src, _)) = do
case txt of case txt of
[Str x] | escapeURI x == src -> -- autolink [Str x] | escapeURI x == src -> -- autolink
do modify $ \s -> s{ stLinks = True } do modify $ \s -> s{ stLinks = True }
@ -283,7 +283,7 @@ inlineToOrg (Link txt (src, _)) = do
_ -> do contents <- inlineListToOrg txt _ -> do contents <- inlineListToOrg txt
modify $ \s -> s{ stLinks = True } modify $ \s -> s{ stLinks = True }
return $ "[[" <> text src <> "][" <> contents <> "]]" return $ "[[" <> text src <> "][" <> contents <> "]]"
inlineToOrg (Image _ (source, _)) = do inlineToOrg (Image _ _ (source, _)) = do
modify $ \s -> s{ stImages = True } modify $ \s -> s{ stImages = True }
return $ "[[" <> text source <> "]]" return $ "[[" <> text source <> "]]"
inlineToOrg (Note contents) = do inlineToOrg (Note contents) = do

View file

@ -35,6 +35,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Options import Text.Pandoc.Options
import Text.Pandoc.Shared import Text.Pandoc.Shared
import Text.Pandoc.Writers.Shared import Text.Pandoc.Writers.Shared
import Text.Pandoc.ImageSize
import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.Builder (deleteMeta) import Text.Pandoc.Builder (deleteMeta)
import Data.Maybe (fromMaybe) import Data.Maybe (fromMaybe)
@ -49,7 +50,7 @@ type Refs = [([Inline], Target)]
data WriterState = data WriterState =
WriterState { stNotes :: [[Block]] WriterState { stNotes :: [[Block]]
, stLinks :: Refs , stLinks :: Refs
, stImages :: [([Inline], (String, String, Maybe String))] , stImages :: [([Inline], (Attr, String, String, Maybe String))]
, stHasMath :: Bool , stHasMath :: Bool
, stHasRawTeX :: Bool , stHasRawTeX :: Bool
, stOptions :: WriterOptions , stOptions :: WriterOptions
@ -138,17 +139,22 @@ noteToRST num note = do
return $ nowrap $ marker $$ nest 3 contents return $ nowrap $ marker $$ nest 3 contents
-- | Return RST representation of picture reference table. -- | Return RST representation of picture reference table.
pictRefsToRST :: [([Inline], (String, String, Maybe String))] pictRefsToRST :: [([Inline], (Attr, String, String, Maybe String))]
-> State WriterState Doc -> State WriterState Doc
pictRefsToRST refs = mapM pictToRST refs >>= return . vcat pictRefsToRST refs = mapM pictToRST refs >>= return . vcat
-- | Return RST representation of a picture substitution reference. -- | Return RST representation of a picture substitution reference.
pictToRST :: ([Inline], (String, String,Maybe String)) pictToRST :: ([Inline], (Attr, String, String, Maybe String))
-> State WriterState Doc -> State WriterState Doc
pictToRST (label, (src, _, mbtarget)) = do pictToRST (label, (attr, src, _, mbtarget)) = do
label' <- inlineListToRST label label' <- inlineListToRST label
dims <- imageDimsToRST attr
let (_, cls, _) = attr
classes = if null cls
then empty
else ":class: " <> text (unwords cls)
return $ nowrap return $ nowrap
$ ".. |" <> label' <> "| image:: " <> text src $ ".. |" <> label' <> "| image:: " <> text src $$ hang 3 empty (classes $$ dims)
$$ case mbtarget of $$ case mbtarget of
Nothing -> empty Nothing -> empty
Just t -> " :target: " <> text t Just t -> " :target: " <> text t
@ -183,11 +189,16 @@ blockToRST (Div attr bs) = do
return $ blankline <> startTag $+$ contents $+$ endTag $$ blankline return $ blankline <> startTag $+$ contents $+$ endTag $$ blankline
blockToRST (Plain inlines) = inlineListToRST inlines blockToRST (Plain inlines) = inlineListToRST inlines
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
blockToRST (Para [Image txt (src,'f':'i':'g':':':tit)]) = do blockToRST (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
capt <- inlineListToRST txt capt <- inlineListToRST txt
dims <- imageDimsToRST attr
let fig = "figure:: " <> text src let fig = "figure:: " <> text src
let alt = ":alt: " <> if null tit then capt else text tit alt = ":alt: " <> if null tit then capt else text tit
return $ hang 3 ".. " (fig $$ alt $+$ capt) $$ blankline (_,cls,_) = attr
classes = if null cls
then empty
else ":figclass: " <> text (unwords cls)
return $ hang 3 ".. " (fig $$ alt $$ classes $$ dims $+$ capt) $$ blankline
blockToRST (Para inlines) blockToRST (Para inlines)
| LineBreak `elem` inlines = do -- use line block if LineBreaks | LineBreak `elem` inlines = do -- use line block if LineBreaks
lns <- mapM inlineListToRST $ splitBy (==LineBreak) inlines lns <- mapM inlineListToRST $ splitBy (==LineBreak) inlines
@ -382,8 +393,8 @@ inlineListToRST lst =
isComplex (Strikeout _) = True isComplex (Strikeout _) = True
isComplex (Superscript _) = True isComplex (Superscript _) = True
isComplex (Subscript _) = True isComplex (Subscript _) = True
isComplex (Link _ _) = True isComplex (Link _ _ _) = True
isComplex (Image _ _) = True isComplex (Image _ _ _) = True
isComplex (Code _ _) = True isComplex (Code _ _) = True
isComplex (Math _ _) = True isComplex (Math _ _) = True
isComplex (Cite _ (x:_)) = isComplex x isComplex (Cite _ (x:_)) = isComplex x
@ -436,17 +447,17 @@ inlineToRST (RawInline f x)
inlineToRST (LineBreak) = return cr -- there's no line break in RST (see Para) inlineToRST (LineBreak) = return cr -- there's no line break in RST (see Para)
inlineToRST Space = return space inlineToRST Space = return space
-- autolink -- autolink
inlineToRST (Link [Str str] (src, _)) inlineToRST (Link _ [Str str] (src, _))
| isURI src && | isURI src &&
if "mailto:" `isPrefixOf` src if "mailto:" `isPrefixOf` src
then src == escapeURI ("mailto:" ++ str) then src == escapeURI ("mailto:" ++ str)
else src == escapeURI str = do else src == escapeURI str = do
let srcSuffix = fromMaybe src (stripPrefix "mailto:" src) let srcSuffix = fromMaybe src (stripPrefix "mailto:" src)
return $ text srcSuffix return $ text srcSuffix
inlineToRST (Link [Image alt (imgsrc,imgtit)] (src, _tit)) = do inlineToRST (Link _ [Image attr alt (imgsrc,imgtit)] (src, _tit)) = do
label <- registerImage alt (imgsrc,imgtit) (Just src) label <- registerImage attr alt (imgsrc,imgtit) (Just src)
return $ "|" <> label <> "|" return $ "|" <> label <> "|"
inlineToRST (Link txt (src, tit)) = do inlineToRST (Link _ txt (src, tit)) = do
useReferenceLinks <- get >>= return . writerReferenceLinks . stOptions useReferenceLinks <- get >>= return . writerReferenceLinks . stOptions
linktext <- inlineListToRST $ normalizeSpaces txt linktext <- inlineListToRST $ normalizeSpaces txt
if useReferenceLinks if useReferenceLinks
@ -461,8 +472,8 @@ inlineToRST (Link txt (src, tit)) = do
modify $ \st -> st { stLinks = (txt,(src,tit)):refs } modify $ \st -> st { stLinks = (txt,(src,tit)):refs }
return $ "`" <> linktext <> "`_" return $ "`" <> linktext <> "`_"
else return $ "`" <> linktext <> " <" <> text src <> ">`__" else return $ "`" <> linktext <> " <" <> text src <> ">`__"
inlineToRST (Image alternate (source, tit)) = do inlineToRST (Image attr alternate (source, tit)) = do
label <- registerImage alternate (source,tit) Nothing label <- registerImage attr alternate (source,tit) Nothing
return $ "|" <> label <> "|" return $ "|" <> label <> "|"
inlineToRST (Note contents) = do inlineToRST (Note contents) = do
-- add to notes in state -- add to notes in state
@ -471,16 +482,33 @@ inlineToRST (Note contents) = do
let ref = show $ (length notes) + 1 let ref = show $ (length notes) + 1
return $ " [" <> text ref <> "]_" return $ " [" <> text ref <> "]_"
registerImage :: [Inline] -> Target -> Maybe String -> State WriterState Doc registerImage :: Attr -> [Inline] -> Target -> Maybe String -> State WriterState Doc
registerImage alt (src,tit) mbtarget = do registerImage attr alt (src,tit) mbtarget = do
pics <- get >>= return . stImages pics <- get >>= return . stImages
txt <- case lookup alt pics of txt <- case lookup alt pics of
Just (s,t,mbt) | (s,t,mbt) == (src,tit,mbtarget) -> return alt Just (a,s,t,mbt) | (a,s,t,mbt) == (attr,src,tit,mbtarget)
-> return alt
_ -> do _ -> do
let alt' = if null alt || alt == [Str ""] let alt' = if null alt || alt == [Str ""]
then [Str $ "image" ++ show (length pics)] then [Str $ "image" ++ show (length pics)]
else alt else alt
modify $ \st -> st { stImages = modify $ \st -> st { stImages =
(alt', (src,tit, mbtarget)):stImages st } (alt', (attr,src,tit, mbtarget)):stImages st }
return alt' return alt'
inlineListToRST txt inlineListToRST txt
imageDimsToRST :: Attr -> State WriterState Doc
imageDimsToRST attr = do
let (ident, _, _) = attr
name = if null ident
then empty
else ":name: " <> text ident
showDim dir = let cols d = ":" <> text (show dir) <> ": " <> text (show d)
in case (dimension dir attr) of
Just (Percent a) ->
case dir of
Height -> empty
Width -> cols (Percent a)
Just dim -> cols dim
Nothing -> empty
return $ cr <> name $$ showDim Width $$ showDim Height

View file

@ -46,7 +46,7 @@ import Text.Pandoc.ImageSize
-- or a MediaBag, or the internet. -- or a MediaBag, or the internet.
-- If file not found or filetype not jpeg or png, leave the inline unchanged. -- If file not found or filetype not jpeg or png, leave the inline unchanged.
rtfEmbedImage :: WriterOptions -> Inline -> IO Inline rtfEmbedImage :: WriterOptions -> Inline -> IO Inline
rtfEmbedImage opts x@(Image _ (src,_)) = do rtfEmbedImage opts x@(Image attr _ (src,_)) = do
result <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src result <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src
case result of case result of
Right (imgdata, Just mime) Right (imgdata, Just mime)
@ -63,12 +63,12 @@ rtfEmbedImage opts x@(Image _ (src,_)) = do
return "" return ""
Right sz -> return $ "\\picw" ++ show xpx ++ Right sz -> return $ "\\picw" ++ show xpx ++
"\\pich" ++ show ypx ++ "\\pich" ++ show ypx ++
"\\picwgoal" ++ show (xpt * 20) "\\picwgoal" ++ show (floor (xpt * 20) :: Integer)
++ "\\pichgoal" ++ show (ypt * 20) ++ "\\pichgoal" ++ show (floor (ypt * 20) :: Integer)
-- twip = 1/1440in = 1/20pt -- twip = 1/1440in = 1/20pt
where (xpx, ypx) = sizeInPixels sz where (xpx, ypx) = sizeInPixels sz
(xpt, ypt) = sizeInPoints sz (xpt, ypt) = desiredSizeInPoints opts attr sz
let raw = "{\\pict" ++ filetype ++ sizeSpec ++ " " ++ let raw = "{\\pict" ++ filetype ++ sizeSpec ++ "\\bin " ++
concat bytes ++ "}" concat bytes ++ "}"
return $ if B.null imgdata return $ if B.null imgdata
then x then x
@ -350,10 +350,10 @@ inlineToRTF (RawInline f str)
| otherwise = "" | otherwise = ""
inlineToRTF (LineBreak) = "\\line " inlineToRTF (LineBreak) = "\\line "
inlineToRTF Space = " " inlineToRTF Space = " "
inlineToRTF (Link text (src, _)) = inlineToRTF (Link _ text (src, _)) =
"{\\field{\\*\\fldinst{HYPERLINK \"" ++ (codeStringToRTF src) ++ "{\\field{\\*\\fldinst{HYPERLINK \"" ++ (codeStringToRTF src) ++
"\"}}{\\fldrslt{\\ul\n" ++ (inlineListToRTF text) ++ "\n}}}\n" "\"}}{\\fldrslt{\\ul\n" ++ (inlineListToRTF text) ++ "\n}}}\n"
inlineToRTF (Image _ (source, _)) = inlineToRTF (Image _ _ (source, _)) =
"{\\cf1 [image: " ++ source ++ "]\\cf0}" "{\\cf1 [image: " ++ source ++ "]\\cf0}"
inlineToRTF (Note contents) = inlineToRTF (Note contents) =
"{\\super\\chftn}{\\*\\footnote\\chftn\\~\\plain\\pard " ++ "{\\super\\chftn}{\\*\\footnote\\chftn\\~\\plain\\pard " ++

View file

@ -40,6 +40,7 @@ import Data.Ord ( comparing )
import Data.Char ( chr, ord ) import Data.Char ( chr, ord )
import Control.Monad.State import Control.Monad.State
import Text.Pandoc.Pretty import Text.Pandoc.Pretty
import Text.Pandoc.ImageSize
import Network.URI ( isURI, unEscapeString ) import Network.URI ( isURI, unEscapeString )
import System.FilePath import System.FilePath
@ -49,6 +50,7 @@ data WriterState =
, stSubscript :: Bool -- document contains subscript , stSubscript :: Bool -- document contains subscript
, stEscapeComma :: Bool -- in a context where we need @comma , stEscapeComma :: Bool -- in a context where we need @comma
, stIdentifiers :: [String] -- header ids used already , stIdentifiers :: [String] -- header ids used already
, stOptions :: WriterOptions -- writer options
} }
{- TODO: {- TODO:
@ -61,7 +63,8 @@ writeTexinfo :: WriterOptions -> Pandoc -> String
writeTexinfo options document = writeTexinfo options document =
evalState (pandocToTexinfo options $ wrapTop document) $ evalState (pandocToTexinfo options $ wrapTop document) $
WriterState { stStrikeout = False, stSuperscript = False, WriterState { stStrikeout = False, stSuperscript = False,
stEscapeComma = False, stSubscript = False, stIdentifiers = [] } stEscapeComma = False, stSubscript = False,
stIdentifiers = [], stOptions = options}
-- | Add a "Top" node around the document, needed by Texinfo. -- | Add a "Top" node around the document, needed by Texinfo.
wrapTop :: Pandoc -> Pandoc wrapTop :: Pandoc -> Pandoc
@ -130,12 +133,12 @@ blockToTexinfo (Plain lst) =
inlineListToTexinfo lst inlineListToTexinfo lst
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
blockToTexinfo (Para [Image txt (src,'f':'i':'g':':':tit)]) = do blockToTexinfo (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
capt <- if null txt capt <- if null txt
then return empty then return empty
else (\c -> text "@caption" <> braces c) `fmap` else (\c -> text "@caption" <> braces c) `fmap`
inlineListToTexinfo txt inlineListToTexinfo txt
img <- inlineToTexinfo (Image txt (src,tit)) img <- inlineToTexinfo (Image attr txt (src,tit))
return $ text "@float" $$ img $$ capt $$ text "@end float" return $ text "@float" $$ img $$ capt $$ text "@end float"
blockToTexinfo (Para lst) = blockToTexinfo (Para lst) =
@ -424,11 +427,11 @@ inlineToTexinfo (RawInline f str)
inlineToTexinfo (LineBreak) = return $ text "@*" <> cr inlineToTexinfo (LineBreak) = return $ text "@*" <> cr
inlineToTexinfo Space = return space inlineToTexinfo Space = return space
inlineToTexinfo (Link txt (src@('#':_), _)) = do inlineToTexinfo (Link _ txt (src@('#':_), _)) = do
contents <- escapeCommas $ inlineListToTexinfo txt contents <- escapeCommas $ inlineListToTexinfo txt
return $ text "@ref" <> return $ text "@ref" <>
braces (text (stringToTexinfo src) <> text "," <> contents) braces (text (stringToTexinfo src) <> text "," <> contents)
inlineToTexinfo (Link txt (src, _)) = do inlineToTexinfo (Link _ txt (src, _)) = do
case txt of case txt of
[Str x] | escapeURI x == src -> -- autolink [Str x] | escapeURI x == src -> -- autolink
do return $ text $ "@url{" ++ x ++ "}" do return $ text $ "@url{" ++ x ++ "}"
@ -437,10 +440,16 @@ inlineToTexinfo (Link txt (src, _)) = do
return $ text ("@uref{" ++ src1 ++ ",") <> contents <> return $ text ("@uref{" ++ src1 ++ ",") <> contents <>
char '}' char '}'
inlineToTexinfo (Image alternate (source, _)) = do inlineToTexinfo (Image attr alternate (source, _)) = do
content <- escapeCommas $ inlineListToTexinfo alternate content <- escapeCommas $ inlineListToTexinfo alternate
return $ text ("@image{" ++ base ++ ",,,") <> content <> text "," <> opts <- gets stOptions
text (ext ++ "}") let showDim dim = case (dimension dim attr) of
(Just (Pixel a)) -> showInInch opts (Pixel a) ++ "in"
(Just (Percent _)) -> ""
(Just d) -> show d
Nothing -> ""
return $ text ("@image{" ++ base ++ ',':(showDim Width) ++ ',':(showDim Height) ++ ",")
<> content <> text "," <> text (ext ++ "}")
where where
ext = drop 1 $ takeExtension source' ext = drop 1 $ takeExtension source'
base = dropExtension source' base = dropExtension source'

View file

@ -34,6 +34,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Options import Text.Pandoc.Options
import Text.Pandoc.Shared import Text.Pandoc.Shared
import Text.Pandoc.Pretty (render) import Text.Pandoc.Pretty (render)
import Text.Pandoc.ImageSize
import Text.Pandoc.Writers.Shared import Text.Pandoc.Writers.Shared
import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Templates (renderTemplate')
import Text.Pandoc.XML ( escapeStringForXML ) import Text.Pandoc.XML ( escapeStringForXML )
@ -116,9 +117,9 @@ blockToTextile opts (Plain inlines) =
inlineListToTextile opts inlines inlineListToTextile opts inlines
-- title beginning with fig: indicates that the image is a figure -- title beginning with fig: indicates that the image is a figure
blockToTextile opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do blockToTextile opts (Para [Image attr txt (src,'f':'i':'g':':':tit)]) = do
capt <- blockToTextile opts (Para txt) capt <- blockToTextile opts (Para txt)
im <- inlineToTextile opts (Image txt (src,tit)) im <- inlineToTextile opts (Image attr txt (src,tit))
return $ im ++ "\n" ++ capt return $ im ++ "\n" ++ capt
blockToTextile opts (Para inlines) = do blockToTextile opts (Para inlines) = do
@ -435,23 +436,39 @@ inlineToTextile _ (LineBreak) = return "\n"
inlineToTextile _ Space = return " " inlineToTextile _ Space = return " "
inlineToTextile opts (Link txt (src, _)) = do inlineToTextile opts (Link (_, cls, _) txt (src, _)) = do
let classes = if null cls
then ""
else "(" ++ unwords cls ++ ")"
label <- case txt of label <- case txt of
[Code _ s] [Code _ s]
| s == src -> return "$" | s == src -> return "$"
[Str s] [Str s]
| s == src -> return "$" | s == src -> return "$"
_ -> inlineListToTextile opts txt _ -> inlineListToTextile opts txt
return $ "\"" ++ label ++ "\":" ++ src return $ "\"" ++ classes ++ label ++ "\":" ++ src
inlineToTextile opts (Image alt (source, tit)) = do inlineToTextile opts (Image attr@(_, cls, _) alt (source, tit)) = do
alt' <- inlineListToTextile opts alt alt' <- inlineListToTextile opts alt
let txt = if null tit let txt = if null tit
then if null alt' then if null alt'
then "" then ""
else "(" ++ alt' ++ ")" else "(" ++ alt' ++ ")"
else "(" ++ tit ++ ")" else "(" ++ tit ++ ")"
return $ "!" ++ source ++ txt ++ "!" classes = if null cls
then ""
else "(" ++ unwords cls ++ ")"
showDim dir = let toCss str = Just $ show dir ++ ":" ++ str ++ ";"
in case (dimension dir attr) of
Just (Percent a) -> toCss $ show (Percent a)
Just dim -> toCss $ showInPixel opts dim ++ "px"
Nothing -> Nothing
styles = case (showDim Width, showDim Height) of
(Just w, Just h) -> "{" ++ w ++ h ++ "}"
(Just w, Nothing) -> "{" ++ w ++ "height:auto;}"
(Nothing, Just h) -> "{" ++ "width:auto;" ++ h ++ "}"
(Nothing, Nothing) -> ""
return $ "!" ++ classes ++ styles ++ source ++ txt ++ "!"
inlineToTextile opts (Note contents) = do inlineToTextile opts (Note contents) = do
curNotes <- liftM stNotes get curNotes <- liftM stNotes get

View file

@ -7,5 +7,13 @@ flags:
network-uri: true network-uri: true
packages: packages:
- '.' - '.'
- location:
git: 'https://github.com/jgm/pandoc-types'
commit: c64eb383dce64396290aa815351ddb6e43cb6b0f
extra-dep: true
- location:
git: 'https://github.com/jgm/texmath'
commit: a716e9b5d8c1634847db2c1119e60836634569bf
extra-dep: true
extra-deps: [] extra-deps: []
resolver: lts-3.13 resolver: lts-3.13

View file

@ -56,14 +56,16 @@ arbInline n = frequency $ [ (60, liftM Str realString)
, (10, do x1 <- arbitrary , (10, do x1 <- arbitrary
x2 <- realString x2 <- realString
return $ Math x1 x2) return $ Math x1 x2)
, (10, do x1 <- arbInlines (n-1) , (10, do x0 <- arbAttr
x1 <- arbInlines (n-1)
x3 <- realString x3 <- realString
x2 <- liftM escapeURI realString x2 <- liftM escapeURI realString
return $ Link x1 (x2,x3)) return $ Link x0 x1 (x2,x3))
, (10, do x1 <- arbInlines (n-1) , (10, do x0 <- arbAttr
x1 <- arbInlines (n-1)
x3 <- realString x3 <- realString
x2 <- liftM escapeURI realString x2 <- liftM escapeURI realString
return $ Image x1 (x2,x3)) return $ Image x0 x1 (x2,x3))
, (2, liftM2 Cite arbitrary (arbInlines 1)) , (2, liftM2 Cite arbitrary (arbInlines 1))
, (2, liftM Note $ resize 3 $ listOf1 $ arbBlock (n-1)) , (2, liftM Note $ resize 3 $ listOf1 $ arbBlock (n-1))
] ]

View file

@ -42,7 +42,7 @@ tests = [ testGroup "code blocks"
, testGroup "definition lists" , testGroup "definition lists"
[ "with internal link" =: definitionList [(link "#go" "" (str "testing"), [ "with internal link" =: definitionList [(link "#go" "" (str "testing"),
[plain (text "hi there")])] =?> [plain (text "hi there")])] =?>
"\\begin{description}\n\\tightlist\n\\item[\\protect\\hyperlink{go}{testing}]\nhi there\n\\end{description}" "\\begin{description}\n\\tightlist\n\\item[{\\protect\\hyperlink{go}{testing}}]\nhi there\n\\end{description}"
] ]
, testGroup "math" , testGroup "math"
[ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?> [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?>

View file

@ -1,7 +1,7 @@
Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]}) Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."] [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,Header 1 ("headers",[],[]) [Str "Headers"] ,Header 1 ("headers",[],[]) [Str "Headers"]
,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embedded",Space,Str "link"] ("/url","")] ,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link ("",[],[]) [Str "embedded",Space,Str "link"] ("/url","")]
,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]] ,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]]
,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"] ,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"]
,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"] ,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"]
@ -179,7 +179,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"] ,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"]
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."] ,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."]
,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."] ,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."]
,Para [Str "An",Space,Emph [Link [Str "emphasized",Space,Str "link"] ("/url","")],Str "."] ,Para [Str "An",Space,Emph [Link ("",[],[]) [Str "emphasized",Space,Str "link"] ("/url","")],Str "."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]] ,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."] ,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]] ,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
@ -230,51 +230,51 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Str "Minus:",Space,Str "-"] ,Para [Str "Minus:",Space,Str "-"]
,Header 1 ("links",[],[]) [Str "Links"] ,Header 1 ("links",[],[]) [Str "Links"]
,Header 2 ("explicit",[],[]) [Str "Explicit"] ,Header 2 ("explicit",[],[]) [Str "Explicit"]
,Para [Str "Just",Space,Str "a",Space,Link [Str "URL"] ("/url/",""),Str "."] ,Para [Str "Just",Space,Str "a",Space,Link ("",[],[]) [Str "URL"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","")] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","")]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","")] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","")]
,Para [Link [Str "with_underscore"] ("/url/with_underscore","")] ,Para [Link ("",[],[]) [Str "with_underscore"] ("/url/with_underscore","")]
,Para [Link [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")] ,Para [Link ("",[],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
,Para [Link [Str "Empty"] ("",""),Str "."] ,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."]
,Header 2 ("reference",[],[]) [Str "Reference"] ,Header 2 ("reference",[],[]) [Str "Reference"]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "With",Space,Link [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."] ,Para [Str "With",Space,Link ("",[],[]) [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."]
,Para [Link [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."] ,Para [Link ("",[],[]) [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."]
,Para [Str "Indented",Space,Link [Str "once"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "once"] ("/url",""),Str "."]
,Para [Str "Indented",Space,Link [Str "twice"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "twice"] ("/url",""),Str "."]
,Para [Str "Indented",Space,Link [Str "thrice"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "thrice"] ("/url",""),Str "."]
,Para [Str "This",Space,Str "should",Space,Str "[not][]",Space,Str "be",Space,Str "a",Space,Str "link."] ,Para [Str "This",Space,Str "should",Space,Str "[not][]",Space,Str "be",Space,Str "a",Space,Str "link."]
,CodeBlock ("",[],[]) "[not]: /url" ,CodeBlock ("",[],[]) "[not]: /url"
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "biz"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "biz"] ("/url/",""),Str "."]
,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"] ,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"]
,Para [Str "Here\8217s",Space,Str "a",Space,Link [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "a",Space,Link ("",[],[]) [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link [Str "AT&T"] ("http://att.com/",""),Str "."] ,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link ("",[],[]) [Str "AT&T"] ("http://att.com/",""),Str "."]
,Para [Str "Here\8217s",Space,Str "an",Space,Link [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
,Para [Str "Here\8217s",Space,Str "an",Space,Link [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."]
,Header 2 ("autolinks",[],[]) [Str "Autolinks"] ,Header 2 ("autolinks",[],[]) [Str "Autolinks"]
,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")] ,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link ("",[],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
,BulletList ,BulletList
[[Para [Str "In",Space,Str "a",Space,Str "list?"]] [[Para [Str "In",Space,Str "a",Space,Str "list?"]]
,[Para [Link [Str "http://example.com/"] ("http://example.com/","")]] ,[Para [Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
,[Para [Str "It",Space,Str "should."]]] ,[Para [Str "It",Space,Str "should."]]]
,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")] ,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",[],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
,BlockQuote ,BlockQuote
[Para [Str "Blockquoted:",Space,Link [Str "http://example.com/"] ("http://example.com/","")]] [Para [Str "Blockquoted:",Space,Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"] ,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"]
,CodeBlock ("",[],[]) "or here: <http://example.com/>" ,CodeBlock ("",[],[]) "or here: <http://example.com/>"
,Header 1 ("images",[],[]) [Str "Images"] ,Header 1 ("images",[],[]) [Str "Images"]
,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"] ,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
,Para [Image [Str "lalune",Space,Str "fig",Space,Str "caption"] ("lalune.jpg","fig:")] ,Para [Image ("",[],[]) [Str "lalune",Space,Str "fig",Space,Str "caption"] ("lalune.jpg","fig:")]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [] ("movie.jpg",""),Space,Str "icon.",Space,Str "And",Space,Str "here",Space,Str "a",Space,Str "second",Space,Str "movie",Space,Image [Str "alt",Space,Str "text"] ("movie.jpg",""),Space,Str "icon.",Space,Str "And",Space,Str "here",Space,Str "a",Space,Str "third",Space,Str "movie",Space,Image [Str "alt",Space,Str "text"] ("movie.jpg",""),Space,Str "icon."] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [] ("movie.jpg",""),Space,Str "icon.",Space,Str "And",Space,Str "here",Space,Str "a",Space,Str "second",Space,Str "movie",Space,Image ("",[],[]) [Str "alt",Space,Str "text"] ("movie.jpg",""),Space,Str "icon.",Space,Str "And",Space,Str "here",Space,Str "a",Space,Str "third",Space,Str "movie",Space,Image ("",[],[]) [Str "alt",Space,Str "text"] ("movie.jpg",""),Space,Str "icon."]
,Para [Image [Str "lalune",Space,Str "no",Space,Str "figure",Space,Str "alt",Space,Str "text"] ("lalune.jpg","")] ,Para [Image ("",[],[]) [Str "lalune",Space,Str "no",Space,Str "figure",Space,Str "alt",Space,Str "text"] ("lalune.jpg","")]
,Header 1 ("footnotes",[],[]) [Str "Footnotes"] ,Header 1 ("footnotes",[],[]) [Str "Footnotes"]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link ("",[],[]) [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]]
,BlockQuote ,BlockQuote
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]] [Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]]
,OrderedList (1,Decimal,DefaultDelim) ,OrderedList (1,Decimal,DefaultDelim)

View file

@ -2,11 +2,11 @@ Pandoc (Meta {unMeta = fromList []})
[Header 1 ("ch01",[],[]) [Str "XRef",Space,Str "Samples"] [Header 1 ("ch01",[],[]) [Str "XRef",Space,Str "Samples"]
,Para [Str "This",Space,Str "paragraph",Space,Str "demonstrates",Space,Str "several",Space,Str "features",Space,Str "of",Space,Str "XRef."] ,Para [Str "This",Space,Str "paragraph",Space,Str "demonstrates",Space,Str "several",Space,Str "features",Space,Str "of",Space,Str "XRef."]
,BulletList ,BulletList
[[Para [Str "A",Space,Str "straight",Space,Str "link",Space,Str "generates",Space,Str "the",Space,Str "cross-reference",Space,Str "text:",Space,Link [Str "The Second Chapter"] ("#ch02",""),Str "."]] [[Para [Str "A",Space,Str "straight",Space,Str "link",Space,Str "generates",Space,Str "the",Space,Str "cross-reference",Space,Str "text:",Space,Link ("",[],[]) [Str "The Second Chapter"] ("#ch02",""),Str "."]]
,[Para [Str "A",Space,Str "link",Space,Str "to",Space,Str "an",Space,Str "element",Space,Str "with",Space,Str "an",Space,Str "XRefLabel:",Space,Link [Str "Chapter the Third"] ("#ch03",""),Str "."]] ,[Para [Str "A",Space,Str "link",Space,Str "to",Space,Str "an",Space,Str "element",Space,Str "with",Space,Str "an",Space,Str "XRefLabel:",Space,Link ("",[],[]) [Str "Chapter the Third"] ("#ch03",""),Str "."]]
,[Para [Str "A",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "EndTerm:",Space,Link [Str "Chapter 4"] ("#ch04",""),Str "."]] ,[Para [Str "A",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "EndTerm:",Space,Link ("",[],[]) [Str "Chapter 4"] ("#ch04",""),Str "."]]
,[Para [Str "A",Space,Str "link",Space,Str "to",Space,Str "an",Space,Str "cmdsynopsis",Space,Str "element:",Space,Link [Str "chgrp"] ("#cmd01",""),Str "."]] ,[Para [Str "A",Space,Str "link",Space,Str "to",Space,Str "an",Space,Str "cmdsynopsis",Space,Str "element:",Space,Link ("",[],[]) [Str "chgrp"] ("#cmd01",""),Str "."]]
,[Para [Str "A",Space,Str "link",Space,Str "to",Space,Str "an",Space,Str "funcsynopsis",Space,Str "element:",Space,Link [Str "max"] ("#func01",""),Str "."]]] ,[Para [Str "A",Space,Str "link",Space,Str "to",Space,Str "an",Space,Str "funcsynopsis",Space,Str "element:",Space,Link ("",[],[]) [Str "max"] ("#func01",""),Str "."]]]
,Header 1 ("ch02",[],[]) [Str "The",Space,Str "Second",Space,Str "Chapter"] ,Header 1 ("ch02",[],[]) [Str "The",Space,Str "Second",Space,Str "Chapter"]
,Para [Str "Some",Space,Str "content",Space,Str "here"] ,Para [Str "Some",Space,Str "content",Space,Str "here"]
,Header 1 ("ch03",[],[]) [Str "The",Space,Str "Third",Space,Str "Chapter"] ,Header 1 ("ch03",[],[]) [Str "The",Space,Str "Third",Space,Str "Chapter"]

View file

@ -1,2 +1,2 @@
[Header 1 ("anchor-header",[],[]) [Str "Anchor",Space,Str "Header"] [Header 1 ("anchor-header",[],[]) [Str "Anchor",Space,Str "Header"]
,Para [Str "A",Space,Link [Str "link"] ("#anchor-header","")]] ,Para [Str "A",Space,Link ("",[],[]) [Str "link"] ("#anchor-header","")]]

View file

@ -1,2 +1,2 @@
[Para [Str "An",Space,Str "image:"] [Para [Str "An",Space,Str "image:"]
,Para [Image [] ("media/image1.jpg","")]] ,Para [Image ("",[],[]) [] ("media/image1.jpg","")]]

View file

@ -1,2 +1,2 @@
[Para [Str "An",Space,Str "image:"] [Para [Str "An",Space,Str "image:"]
,Para [Image [] ("media/rId25.jpg","")]] ,Para [Image ("",[],[]) [] ("media/rId25.jpg","")]]

View file

@ -1,4 +1,4 @@
[Header 1 ("vml-image",[],[]) [Strong [Str "VML",Space,Str "Image"]] [Header 1 ("vml-image",[],[]) [Strong [Str "VML",Space,Str "Image"]]
,BlockQuote ,BlockQuote
[Para [Str "It",Space,Str "should",Space,Str "follow",Space,Str "below:"] [Para [Str "It",Space,Str "should",Space,Str "follow",Space,Str "below:"]
,Para [Image [] ("media/image4.jpeg","")]]] ,Para [Image ("",[],[]) [] ("media/image4.jpeg","")]]]

View file

@ -1,2 +1,2 @@
[Para [Str "This",Space,Str "picture",Space,Image [] ("media/image1.jpg",""),Space,Str "is",Space,Str "an",Space,Str "identicon."] [Para [Str "This",Space,Str "picture",Space,Image ("",[],[]) [] ("media/image1.jpg",""),Space,Str "is",Space,Str "an",Space,Str "identicon."]
,Para [Str "Here",Space,Str "is",Space,Link [Str "one",Space,Image [] ("media/image2.jpg",""),Space,Str "that"] ("http://www.google.com",""),Space,Str "links."]] ,Para [Str "Here",Space,Str "is",Space,Link ("",[],[]) [Str "one",Space,Image ("",[],[]) [] ("media/image2.jpg",""),Space,Str "that"] ("http://www.google.com",""),Space,Str "links."]]

View file

@ -1,2 +1,2 @@
[Para [Str "This",Space,Str "picture",Space,Image [] ("media/rId26.jpg",""),Space,Str "is",Space,Str "an",Space,Str "identicon."] [Para [Str "This",Space,Str "picture",Space,Image ("",[],[]) [] ("media/rId26.jpg",""),Space,Str "is",Space,Str "an",Space,Str "identicon."]
,Para [Str "Here",Space,Str "is",Space,Link [Str "one",Space,Image [] ("media/rId27.jpg",""),Space,Str "that"] ("http://www.google.com",""),Space,Str "links."]] ,Para [Str "Here",Space,Str "is",Space,Link ("",[],[]) [Str "one",Space,Image ("",[],[]) [] ("media/rId27.jpg",""),Space,Str "that"] ("http://www.google.com",""),Space,Str "links."]]

View file

@ -1 +1 @@
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "test",Note [Para [Link [Str "http://wikipedia.org/"] ("http://wikipedia.org/","")]],Str "."]] [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "test",Note [Para [Link ("",[],[]) [Str "http://wikipedia.org/"] ("http://wikipedia.org/","")]],Str "."]]

View file

@ -1,7 +1,7 @@
[Header 2 ("an-internal-link-and-an-external-link",[],[]) [Str "An",Space,Str "internal",Space,Str "link",Space,Str "and",Space,Str "an",Space,Str "external",Space,Str "link"] [Header 2 ("an-internal-link-and-an-external-link",[],[]) [Str "An",Space,Str "internal",Space,Str "link",Space,Str "and",Space,Str "an",Space,Str "external",Space,Str "link"]
,Para [Str "An",Space,Link [Str "external",Space,Str "link"] ("http://google.com",""),Space,Str "to",Space,Str "a",Space,Str "popular",Space,Str "website."] ,Para [Str "An",Space,Link ("",[],[]) [Str "external",Space,Str "link"] ("http://google.com",""),Space,Str "to",Space,Str "a",Space,Str "popular",Space,Str "website."]
,Para [Str "An",Space,Link [Str "external",Space,Str "link"] ("http://pandoc.org/README.html#synopsis",""),Space,Str "to",Space,Str "a",Space,Str "website",Space,Str "with",Space,Str "an",Space,Str "anchor."] ,Para [Str "An",Space,Link ("",[],[]) [Str "external",Space,Str "link"] ("http://pandoc.org/README.html#synopsis",""),Space,Str "to",Space,Str "a",Space,Str "website",Space,Str "with",Space,Str "an",Space,Str "anchor."]
,Para [Str "An",Space,Link [Str "internal",Space,Str "link"] ("#a-section-for-testing-link-targets",""),Space,Str "to",Space,Str "a",Space,Str "section",Space,Str "header."] ,Para [Str "An",Space,Link ("",[],[]) [Str "internal",Space,Str "link"] ("#a-section-for-testing-link-targets",""),Space,Str "to",Space,Str "a",Space,Str "section",Space,Str "header."]
,Para [Str "An",Space,Link [Str "internal",Space,Str "link"] ("#my_bookmark",""),Space,Str "to",Space,Str "a",Space,Str "bookmark."] ,Para [Str "An",Space,Link ("",[],[]) [Str "internal",Space,Str "link"] ("#my_bookmark",""),Space,Str "to",Space,Str "a",Space,Str "bookmark."]
,Header 2 ("a-section-for-testing-link-targets",[],[]) [Str "A",Space,Str "section",Space,Str "for",Space,Str "testing",Space,Str "link",Space,Str "targets"] ,Header 2 ("a-section-for-testing-link-targets",[],[]) [Str "A",Space,Str "section",Space,Str "for",Space,Str "testing",Space,Str "link",Space,Str "targets"]
,Para [Str "A",Space,Str "bookmark",Space,Str "right",Space,Span ("my_bookmark",["anchor"],[]) [],Str "here"]] ,Para [Str "A",Space,Str "bookmark",Space,Str "right",Space,Span ("my_bookmark",["anchor"],[]) [],Str "here"]]

View file

@ -1,6 +1,6 @@
[Header 2 ("an-internal-link-and-an-external-link",[],[]) [Str "An",Space,Str "internal",Space,Str "link",Space,Str "and",Space,Str "an",Space,Str "external",Space,Str "link"] [Header 2 ("an-internal-link-and-an-external-link",[],[]) [Str "An",Space,Str "internal",Space,Str "link",Space,Str "and",Space,Str "an",Space,Str "external",Space,Str "link"]
,Para [Str "An",Space,Link [Str "external",Space,Str "link"] ("http://google.com",""),Space,Str "to",Space,Str "a",Space,Str "popular",Space,Str "website."] ,Para [Str "An",Space,Link ("",[],[]) [Str "external",Space,Str "link"] ("http://google.com",""),Space,Str "to",Space,Str "a",Space,Str "popular",Space,Str "website."]
,Para [Str "An",Space,Link [Str "external",Space,Str "link"] ("http://pandoc.org/README.html#synopsis",""),Space,Str "to",Space,Str "a",Space,Str "website",Space,Str "with",Space,Str "an",Space,Str "anchor."] ,Para [Str "An",Space,Link ("",[],[]) [Str "external",Space,Str "link"] ("http://pandoc.org/README.html#synopsis",""),Space,Str "to",Space,Str "a",Space,Str "website",Space,Str "with",Space,Str "an",Space,Str "anchor."]
,Para [Str "An",Space,Link [Str "internal",Space,Str "link"] ("#a-section-for-testing-link-targets",""),Space,Str "to",Space,Str "a",Space,Str "section",Space,Str "header."] ,Para [Str "An",Space,Link ("",[],[]) [Str "internal",Space,Str "link"] ("#a-section-for-testing-link-targets",""),Space,Str "to",Space,Str "a",Space,Str "section",Space,Str "header."]
,Para [Str "An",Space,Link [Str "internal",Space,Str "link"] ("#my_bookmark",""),Space,Str "to",Space,Str "a",Space,Str "bookmark."] ,Para [Str "An",Space,Link ("",[],[]) [Str "internal",Space,Str "link"] ("#my_bookmark",""),Space,Str "to",Space,Str "a",Space,Str "bookmark."]
,Header 2 ("a-section-for-testing-link-targets",[],[]) [Str "A",Space,Str "section",Space,Str "for",Space,Str "testing",Space,Str "link",Space,Str "targets"]] ,Header 2 ("a-section-for-testing-link-targets",[],[]) [Str "A",Space,Str "section",Space,Str "for",Space,Str "testing",Space,Str "link",Space,Str "targets"]]

View file

@ -1 +1 @@
[Para [Image [Str "HTTPS",Space,Str "image"] ("https://cooluri.com/image.png",""),Space,Image [Str "HTTP",Space,Str "image"] ("http://cooluri.com/image.png",""),Space,Image [Str "FTP",Space,Str "image"] ("ftp://ftp.cooluri.com/image.png",""),Space,Image [Str "Filesystem",Space,Str "image"] ("file:///tmp/coolimage.png",""),Space,Image [Str "Relative",Space,Str "image",Space,Str "1"] ("/image.jpg",""),Space,Image [Str "Relative",Space,Str "image",Space,Str "2"] ("image.jpg","")]] [Para [Image ("",[],[]) [Str "HTTPS",Space,Str "image"] ("https://cooluri.com/image.png",""),Space,Image ("",[],[]) [Str "HTTP",Space,Str "image"] ("http://cooluri.com/image.png",""),Space,Image ("",[],[]) [Str "FTP",Space,Str "image"] ("ftp://ftp.cooluri.com/image.png",""),Space,Image ("",[],[]) [Str "Filesystem",Space,Str "image"] ("file:///tmp/coolimage.png",""),Space,Image ("",[],[]) [Str "Relative",Space,Str "image",Space,Str "1"] ("/image.jpg",""),Space,Image ("",[],[]) [Str "Relative",Space,Str "image",Space,Str "2"] ("image.jpg","")]]

View file

@ -5,13 +5,13 @@
[Header 2 ("",[],[]) [Str "Status",Space,Str "of",Space,Str "this",Space,Str "Document"] [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 "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 "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"] ("http://idpf.org/","")] ,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"] ("http://idpf.org/","")]
,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:"] ,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) ,OrderedList (1,DefaultStyle,DefaultDelim)
[[Plain [Str "."]]]] [[Plain [Str "."]]]]
,Div ("",["section"],[]) ,Div ("",["section"],[])
[Header 2 ("",[],[]) [Str "About",Space,Str "this",Space,Str "Document"] [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"] ("https://github.com/mgylling/epub-testsuite/wiki/Overview",""),Space,Str "(",Code ("",[],[]) "https://github.com/mgylling/epub-testsuite/wiki/Overview",Str ")",Space,Str "for",Space,Str "additional",Space,Str "information."]] ,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"] ("https://github.com/mgylling/epub-testsuite/wiki/Overview",""),Space,Str "(",Code ("",[],[]) "https://github.com/mgylling/epub-testsuite/wiki/Overview",Str ")",Space,Str "for",Space,Str "additional",Space,Str "information."]]
,Div ("",["section"],[]) ,Div ("",["section"],[])
[Header 2 ("",[],[]) [Str "Conventions"] [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:"] ,Para [Str "The",Space,Str "following",Space,Str "conventions",Space,Str "are",Space,Str "used",Space,Str "throughout",Space,Str "the",Space,Str "document:"]
@ -66,7 +66,7 @@
[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"] [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 [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."]
,Plain [Math DisplayMath "\\begin{array}{llllllllll}\n & {\\operatorname{cov}\\left( \\mathcal{L} \\right)} & \\longrightarrow & {\\operatorname{non}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cof}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cof}\\left( \\mathcal{L} \\right)} & \\longrightarrow & 2^{\\aleph_{0}} \\\\\n & \\uparrow & & \\uparrow & & \\uparrow & & \\uparrow & & \\\\\n & {\\mathfrak{b}} & \\longrightarrow & {\\mathfrak{d}} & & & & & & \\\\\n & \\uparrow & & \\uparrow & & & & & & \\\\\n\\aleph_{1} & \\longrightarrow & {\\operatorname{add}\\left( \\mathcal{L} \\right)} & \\longrightarrow & {\\operatorname{add}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cov}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{non}\\left( \\mathcal{L} \\right)} & \\\\\n\\end{array}"] ,Plain [Math DisplayMath "\\begin{array}{llllllllll}\n & {\\operatorname{cov}\\left( \\mathcal{L} \\right)} & \\longrightarrow & {\\operatorname{non}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cof}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cof}\\left( \\mathcal{L} \\right)} & \\longrightarrow & 2^{\\aleph_{0}} \\\\\n & \\uparrow & & \\uparrow & & \\uparrow & & \\uparrow & & \\\\\n & {\\mathfrak{b}} & \\longrightarrow & {\\mathfrak{d}} & & & & & & \\\\\n & \\uparrow & & \\uparrow & & & & & & \\\\\n\\aleph_{1} & \\longrightarrow & {\\operatorname{add}\\left( \\mathcal{L} \\right)} & \\longrightarrow & {\\operatorname{add}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cov}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{non}\\left( \\mathcal{L} \\right)} & \\\\\n\\end{array}"]
,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Link [Str "Cicho\324's",Space,Str "Diagram"] ("http://en.wikipedia.org/wiki/Cicho%C5%84's_diagram",""),Str ":",Space,Str "."]] ,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Link ("",[],[]) [Str "Cicho\324's",Space,Str "Diagram"] ("http://en.wikipedia.org/wiki/Cicho%C5%84's_diagram",""),Str ":",Space,Str "."]]
,Div ("content-mathml-001.xhtml#mathml-026",["section","ctest"],[]) ,Div ("content-mathml-001.xhtml#mathml-026",["section","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"] [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 [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."]

View file

@ -5,13 +5,13 @@
[Header 2 ("",[],[]) [Str "Status",Space,Str "of",Space,Str "this",Space,Str "Document"] [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 "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 "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"] ("http://idpf.org/","")] ,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"] ("http://idpf.org/","")]
,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:"] ,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) ,OrderedList (1,DefaultStyle,DefaultDelim)
[[Plain [Str "."]]]] [[Plain [Str "."]]]]
,Div ("",["section"],[]) ,Div ("",["section"],[])
[Header 2 ("",[],[]) [Str "About",Space,Str "this",Space,Str "Document"] [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"] ("https://github.com/mgylling/epub-testsuite/wiki/Overview",""),Space,Str "(",Code ("",[],[]) "https://github.com/mgylling/epub-testsuite/wiki/Overview",Str ")",Space,Str "for",Space,Str "additional",Space,Str "information."]] ,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"] ("https://github.com/mgylling/epub-testsuite/wiki/Overview",""),Space,Str "(",Code ("",[],[]) "https://github.com/mgylling/epub-testsuite/wiki/Overview",Str ")",Space,Str "for",Space,Str "additional",Space,Str "information."]]
,Div ("",["section"],[]) ,Div ("",["section"],[])
[Header 2 ("",[],[]) [Str "Conventions"] [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:"] ,Para [Str "The",Space,Str "following",Space,Str "conventions",Space,Str "are",Space,Str "used",Space,Str "throughout",Space,Str "the",Space,Str "document:"]
@ -389,12 +389,12 @@
[Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "style-410"],Space,Code ("",[],[]) "over"] [Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "style-410"],Space,Code ("",[],[]) "over"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "-epub-ruby-position",Space,Str "property",Space,Str "set",Space,Str "to",Space,Str "over",Space,Str "is",Space,Str "supported."] ,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "-epub-ruby-position",Space,Str "property",Space,Str "set",Space,Str "to",Space,Str "over",Space,Str "is",Space,Str "supported."]
,Plain [RawInline (Format "html") "<ruby class=\"ruby-over\">",Strong [Str "Lorem",Space,Str "Ipsum"],Space,RawInline (Format "html") "<rp>",Str "(",RawInline (Format "html") "</rp>",RawInline (Format "html") "<rt>",Str "Lorem",Space,Str "Ipsum",RawInline (Format "html") "</rt>",RawInline (Format "html") "<rp>",Str ")",RawInline (Format "html") "</rp>",RawInline (Format "html") "</ruby>"] ,Plain [RawInline (Format "html") "<ruby class=\"ruby-over\">",Strong [Str "Lorem",Space,Str "Ipsum"],Space,RawInline (Format "html") "<rp>",Str "(",RawInline (Format "html") "</rp>",RawInline (Format "html") "<rt>",Str "Lorem",Space,Str "Ipsum",RawInline (Format "html") "</rt>",RawInline (Format "html") "<rp>",Str ")",RawInline (Format "html") "</rp>",RawInline (Format "html") "</ruby>"]
,Para [Str "If",Space,Str "the",Space,Str "Ruby",Space,Str "text",Space,Str "is",Space,Str "positioned",Space,Str "on",Space,Str "the",Space,Link [Str "over"] ("http://www.w3.org/TR/css3-writing-modes/#over",""),Space,Str "side",Space,Str "of",Space,Str "the",Space,Str "ruby",Space,Str "base,",Space,Str "the",Space,Str "test",Space,Str "passes."]] ,Para [Str "If",Space,Str "the",Space,Str "Ruby",Space,Str "text",Space,Str "is",Space,Str "positioned",Space,Str "on",Space,Str "the",Space,Link ("",[],[]) [Str "over"] ("http://www.w3.org/TR/css3-writing-modes/#over",""),Space,Str "side",Space,Str "of",Space,Str "the",Space,Str "ruby",Space,Str "base,",Space,Str "the",Space,Str "test",Space,Str "passes."]]
,Div ("styling-xhtml-006.xhtml#style-411",["section","ctest"],[]) ,Div ("styling-xhtml-006.xhtml#style-411",["section","ctest"],[])
[Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "style-411"],Space,Code ("",[],[]) "under"] [Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "style-411"],Space,Code ("",[],[]) "under"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "-epub-ruby-position",Space,Str "property",Space,Str "set",Space,Str "to",Space,Str "under",Space,Str "is",Space,Str "supported."] ,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "-epub-ruby-position",Space,Str "property",Space,Str "set",Space,Str "to",Space,Str "under",Space,Str "is",Space,Str "supported."]
,Plain [RawInline (Format "html") "<ruby class=\"ruby-under\">",Strong [Str "Lorem",Space,Str "Ipsum"],Space,RawInline (Format "html") "<rp>",Str "(",RawInline (Format "html") "</rp>",RawInline (Format "html") "<rt>",Str "Lorem",Space,Str "Ipsum",RawInline (Format "html") "</rt>",RawInline (Format "html") "<rp>",Str ")",RawInline (Format "html") "</rp>",RawInline (Format "html") "</ruby>"] ,Plain [RawInline (Format "html") "<ruby class=\"ruby-under\">",Strong [Str "Lorem",Space,Str "Ipsum"],Space,RawInline (Format "html") "<rp>",Str "(",RawInline (Format "html") "</rp>",RawInline (Format "html") "<rt>",Str "Lorem",Space,Str "Ipsum",RawInline (Format "html") "</rt>",RawInline (Format "html") "<rp>",Str ")",RawInline (Format "html") "</rp>",RawInline (Format "html") "</ruby>"]
,Para [Str "If",Space,Str "the",Space,Str "Ruby",Space,Str "text",Space,Str "is",Space,Str "positioned",Space,Str "on",Space,Str "the",Space,Link [Str "under"] ("http://www.w3.org/TR/css3-writing-modes/#under",""),Space,Str "side",Space,Str "of",Space,Str "the",Space,Str "ruby",Space,Str "base,",Space,Str "the",Space,Str "test",Space,Str "passes."]] ,Para [Str "If",Space,Str "the",Space,Str "Ruby",Space,Str "text",Space,Str "is",Space,Str "positioned",Space,Str "on",Space,Str "the",Space,Link ("",[],[]) [Str "under"] ("http://www.w3.org/TR/css3-writing-modes/#under",""),Space,Str "side",Space,Str "of",Space,Str "the",Space,Str "ruby",Space,Str "base,",Space,Str "the",Space,Str "test",Space,Str "passes."]]
,Div ("styling-xhtml-006.xhtml#style-412",["section","ctest"],[]) ,Div ("styling-xhtml-006.xhtml#style-412",["section","ctest"],[])
[Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "style-412"],Space,Code ("",[],[]) "inter-character"] [Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "style-412"],Space,Code ("",[],[]) "inter-character"]
,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "-epub-ruby-position",Space,Str "property",Space,Str "set",Space,Str "to",Space,Str "inter-caracter",Space,Str "is",Space,Str "supported."] ,Para [Str "Tests",Space,Str "whether",Space,Str "the",Space,Code ("",[],[]) "-epub-ruby-position",Space,Str "property",Space,Str "set",Space,Str "to",Space,Str "inter-caracter",Space,Str "is",Space,Str "supported."]

View file

@ -1,4 +1,4 @@
[Para [Image [] ("wasteland-cover.jpg","")] [Para [Image ("",[],[]) [] ("wasteland-cover.jpg","")]
,Para [Span ("wasteland-content.xhtml",[],[]) []] ,Para [Span ("wasteland-content.xhtml",[],[]) []]
,Div ("wasteland-content.xhtml#frontmatter",["section"],[("type","frontmatter")]) ,Div ("wasteland-content.xhtml#frontmatter",["section"],[("type","frontmatter")])
[] []
@ -46,13 +46,13 @@
[Div ("",[],[]) [Div ("",[],[])
[Plain [Str "What",Space,Str "are",Space,Str "the",Space,Str "roots",Space,Str "that",Space,Str "clutch,",Space,Str "what",Space,Str "branches",Space,Str "grow"]] [Plain [Str "What",Space,Str "are",Space,Str "the",Space,Str "roots",Space,Str "that",Space,Str "clutch,",Space,Str "what",Space,Str "branches",Space,Str "grow"]]
,Div ("wasteland-content.xhtml#ln20",[],[]) ,Div ("wasteland-content.xhtml#ln20",[],[])
[Plain [Str "Out",Space,Str "of",Space,Str "this",Space,Str "stony",Space,Str "rubbish?",Space,Str "Son",Space,Str "of",Space,Str "man,",Note [Para [Link [Str "Line",Space,Str "20."] ("#wasteland-content.xhtml#ln20",""),Space,Str "Cf.",Space,Str "Ezekiel",Space,Str "2:1."]]] [Plain [Str "Out",Space,Str "of",Space,Str "this",Space,Str "stony",Space,Str "rubbish?",Space,Str "Son",Space,Str "of",Space,Str "man,",Note [Para [Link ("",[],[]) [Str "Line",Space,Str "20."] ("#wasteland-content.xhtml#ln20",""),Space,Str "Cf.",Space,Str "Ezekiel",Space,Str "2:1."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "You",Space,Str "cannot",Space,Str "say,",Space,Str "or",Space,Str "guess,",Space,Str "for",Space,Str "you",Space,Str "know",Space,Str "only"]] [Plain [Str "You",Space,Str "cannot",Space,Str "say,",Space,Str "or",Space,Str "guess,",Space,Str "for",Space,Str "you",Space,Str "know",Space,Str "only"]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "A",Space,Str "heap",Space,Str "of",Space,Str "broken",Space,Str "images,",Space,Str "where",Space,Str "the",Space,Str "sun",Space,Str "beats,"]] [Plain [Str "A",Space,Str "heap",Space,Str "of",Space,Str "broken",Space,Str "images,",Space,Str "where",Space,Str "the",Space,Str "sun",Space,Str "beats,"]]
,Div ("wasteland-content.xhtml#ln23",[],[]) ,Div ("wasteland-content.xhtml#ln23",[],[])
[Plain [Str "And",Space,Str "the",Space,Str "dead",Space,Str "tree",Space,Str "gives",Space,Str "no",Space,Str "shelter,",Space,Str "the",Space,Str "cricket",Space,Str "no",Space,Str "relief,",Note [Para [Link [Str "23."] ("#wasteland-content.xhtml#ln23",""),Space,Str "Cf.",Space,Str "Ecclesiastes",Space,Str "12:5."]]] [Plain [Str "And",Space,Str "the",Space,Str "dead",Space,Str "tree",Space,Str "gives",Space,Str "no",Space,Str "shelter,",Space,Str "the",Space,Str "cricket",Space,Str "no",Space,Str "relief,",Note [Para [Link ("",[],[]) [Str "23."] ("#wasteland-content.xhtml#ln23",""),Space,Str "Cf.",Space,Str "Ecclesiastes",Space,Str "12:5."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "And",Space,Str "the",Space,Str "dry",Space,Str "stone",Space,Str "no",Space,Str "sound",Space,Str "of",Space,Str "water.",Space,Str "Only"]] [Plain [Str "And",Space,Str "the",Space,Str "dry",Space,Str "stone",Space,Str "no",Space,Str "sound",Space,Str "of",Space,Str "water.",Space,Str "Only"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -70,7 +70,7 @@
,BlockQuote ,BlockQuote
[Div ("",[],[]) [Div ("",[],[])
[Div ("wasteland-content.xhtml#ln31",[],[]) [Div ("wasteland-content.xhtml#ln31",[],[])
[Plain [Str "Frisch",Space,Str "weht",Space,Str "der",Space,Str "Wind",Note [Para [Link [Str "31."] ("#wasteland-content.xhtml#ln31",""),Space,Str "V.",Space,Str "Tristan",Space,Str "und",Space,Str "Isolde,",Space,Str "i,",Space,Str "verses",Space,Str "5-8."]]] [Plain [Str "Frisch",Space,Str "weht",Space,Str "der",Space,Str "Wind",Note [Para [Link ("",[],[]) [Str "31."] ("#wasteland-content.xhtml#ln31",""),Space,Str "V.",Space,Str "Tristan",Space,Str "und",Space,Str "Isolde,",Space,Str "i,",Space,Str "verses",Space,Str "5-8."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Der",Space,Str "Heimat",Space,Str "zu"]] [Plain [Str "Der",Space,Str "Heimat",Space,Str "zu"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -93,7 +93,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Looking",Space,Str "into",Space,Str "the",Space,Str "heart",Space,Str "of",Space,Str "light,",Space,Str "the",Space,Str "silence."]] [Plain [Str "Looking",Space,Str "into",Space,Str "the",Space,Str "heart",Space,Str "of",Space,Str "light,",Space,Str "the",Space,Str "silence."]]
,Div ("wasteland-content.xhtml#ln42",[],[("lang","de")]) ,Div ("wasteland-content.xhtml#ln42",[],[("lang","de")])
[Plain [Emph [Str "Od'",Space,Str "und",Space,Str "leer",Space,Str "das",Space,Str "Meer"],Str ".",Note [Para [Link [Str "42."] ("#wasteland-content.xhtml#ln42",""),Space,Str "Id.",Space,Str "iii,",Space,Str "verse",Space,Str "24."]]] [Plain [Emph [Str "Od'",Space,Str "und",Space,Str "leer",Space,Str "das",Space,Str "Meer"],Str ".",Note [Para [Link ("",[],[]) [Str "42."] ("#wasteland-content.xhtml#ln42",""),Space,Str "Id.",Space,Str "iii,",Space,Str "verse",Space,Str "24."]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("",[],[]) [Div ("",[],[])
[Plain [Str "Madame",Space,Str "Sosostris,",Space,Str "famous",Space,Str "clairvoyante,"]] [Plain [Str "Madame",Space,Str "Sosostris,",Space,Str "famous",Space,Str "clairvoyante,"]]
@ -102,7 +102,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Is",Space,Str "known",Space,Str "to",Space,Str "be",Space,Str "the",Space,Str "wisest",Space,Str "woman",Space,Str "in",Space,Str "Europe,"]] [Plain [Str "Is",Space,Str "known",Space,Str "to",Space,Str "be",Space,Str "the",Space,Str "wisest",Space,Str "woman",Space,Str "in",Space,Str "Europe,"]]
,Div ("wasteland-content.xhtml#ln46",[],[]) ,Div ("wasteland-content.xhtml#ln46",[],[])
[Plain [Str "With",Space,Str "a",Space,Str "wicked",Space,Str "pack",Space,Str "of",Space,Str "cards.",Space,Str "Here,",Space,Str "said",Space,Str "she,",Note [Para [Link [Str "46."] ("#wasteland-content.xhtml#ln46",""),Space,Str "I",Space,Str "am",Space,Str "not",Space,Str "familiar",Space,Str "with",Space,Str "the",Space,Str "exact",Space,Str "constitution",Space,Str "of",Space,Str "the",Space,Str "Tarot",Space,Str "pack",Space,Str "of",Space,Str "cards,",Space,Str "from",Space,Str "which",Space,Str "I",Space,Str "have",Space,Str "obviously",Space,Str "departed",Space,Str "to",Space,Str "suit",Space,Str "my",Space,Str "own",Space,Str "convenience.",Space,Str "The",Space,Str "Hanged",Space,Str "Man,",Space,Str "a",Space,Str "member",Space,Str "of",Space,Str "the",Space,Str "traditional",Space,Str "pack,",Space,Str "fits",Space,Str "my",Space,Str "purpose",Space,Str "in",Space,Str "two",Space,Str "ways:",Space,Str "because",Space,Str "he",Space,Str "is",Space,Str "associated",Space,Str "in",Space,Str "my",Space,Str "mind",Space,Str "with",Space,Str "the",Space,Str "Hanged",Space,Str "God",Space,Str "of",Space,Str "Frazer,",Space,Str "and",Space,Str "because",Space,Str "I",Space,Str "associate",Space,Str "him",Space,Str "with",Space,Str "the",Space,Str "hooded",Space,Str "figure",Space,Str "in",Space,Str "the",Space,Str "passage",Space,Str "of",Space,Str "the",Space,Str "disciples",Space,Str "to",Space,Str "Emmaus",Space,Str "in",Space,Str "Part",Space,Str "V.",Space,Str "The",Space,Str "Phoenician",Space,Str "Sailor",Space,Str "and",Space,Str "the",Space,Str "Merchant",Space,Str "appear",Space,Str "later;",Space,Str "also",Space,Str "the",Space,Str "\"crowds",Space,Str "of",Space,Str "people,\"",Space,Str "and",Space,Str "Death",Space,Str "by",Space,Str "Water",Space,Str "is",Space,Str "executed",Space,Str "in",Space,Str "Part",Space,Str "IV.",Space,Str "The",Space,Str "Man",Space,Str "with",Space,Str "Three",Space,Str "Staves",Space,Str "(an",Space,Str "authentic",Space,Str "member",Space,Str "of",Space,Str "the",Space,Str "Tarot",Space,Str "pack)",Space,Str "I",Space,Str "associate,",Space,Str "quite",Space,Str "arbitrarily,",Space,Str "with",Space,Str "the",Space,Str "Fisher",Space,Str "King",Space,Str "himself."]]] [Plain [Str "With",Space,Str "a",Space,Str "wicked",Space,Str "pack",Space,Str "of",Space,Str "cards.",Space,Str "Here,",Space,Str "said",Space,Str "she,",Note [Para [Link ("",[],[]) [Str "46."] ("#wasteland-content.xhtml#ln46",""),Space,Str "I",Space,Str "am",Space,Str "not",Space,Str "familiar",Space,Str "with",Space,Str "the",Space,Str "exact",Space,Str "constitution",Space,Str "of",Space,Str "the",Space,Str "Tarot",Space,Str "pack",Space,Str "of",Space,Str "cards,",Space,Str "from",Space,Str "which",Space,Str "I",Space,Str "have",Space,Str "obviously",Space,Str "departed",Space,Str "to",Space,Str "suit",Space,Str "my",Space,Str "own",Space,Str "convenience.",Space,Str "The",Space,Str "Hanged",Space,Str "Man,",Space,Str "a",Space,Str "member",Space,Str "of",Space,Str "the",Space,Str "traditional",Space,Str "pack,",Space,Str "fits",Space,Str "my",Space,Str "purpose",Space,Str "in",Space,Str "two",Space,Str "ways:",Space,Str "because",Space,Str "he",Space,Str "is",Space,Str "associated",Space,Str "in",Space,Str "my",Space,Str "mind",Space,Str "with",Space,Str "the",Space,Str "Hanged",Space,Str "God",Space,Str "of",Space,Str "Frazer,",Space,Str "and",Space,Str "because",Space,Str "I",Space,Str "associate",Space,Str "him",Space,Str "with",Space,Str "the",Space,Str "hooded",Space,Str "figure",Space,Str "in",Space,Str "the",Space,Str "passage",Space,Str "of",Space,Str "the",Space,Str "disciples",Space,Str "to",Space,Str "Emmaus",Space,Str "in",Space,Str "Part",Space,Str "V.",Space,Str "The",Space,Str "Phoenician",Space,Str "Sailor",Space,Str "and",Space,Str "the",Space,Str "Merchant",Space,Str "appear",Space,Str "later;",Space,Str "also",Space,Str "the",Space,Str "\"crowds",Space,Str "of",Space,Str "people,\"",Space,Str "and",Space,Str "Death",Space,Str "by",Space,Str "Water",Space,Str "is",Space,Str "executed",Space,Str "in",Space,Str "Part",Space,Str "IV.",Space,Str "The",Space,Str "Man",Space,Str "with",Space,Str "Three",Space,Str "Staves",Space,Str "(an",Space,Str "authentic",Space,Str "member",Space,Str "of",Space,Str "the",Space,Str "Tarot",Space,Str "pack)",Space,Str "I",Space,Str "associate,",Space,Str "quite",Space,Str "arbitrarily,",Space,Str "with",Space,Str "the",Space,Str "Fisher",Space,Str "King",Space,Str "himself."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Is",Space,Str "your",Space,Str "card,",Space,Str "the",Space,Str "drowned",Space,Str "Phoenician",Space,Str "Sailor,"]] [Plain [Str "Is",Space,Str "your",Space,Str "card,",Space,Str "the",Space,Str "drowned",Space,Str "Phoenician",Space,Str "Sailor,"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -131,15 +131,15 @@
[Plain [Str "One",Space,Str "must",Space,Str "be",Space,Str "so",Space,Str "careful",Space,Str "these",Space,Str "days."]]] [Plain [Str "One",Space,Str "must",Space,Str "be",Space,Str "so",Space,Str "careful",Space,Str "these",Space,Str "days."]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("wasteland-content.xhtml#ln60",[],[]) [Div ("wasteland-content.xhtml#ln60",[],[])
[Plain [Str "Unreal",Space,Str "City,",Note [Para [Link [Str "60."] ("#wasteland-content.xhtml#ln60",""),Space,Str "Cf.",Space,Str "Baudelaire:"],BlockQuote [Para [Str "\"Fourmillante",Space,Str "cite;,",Space,Str "cite;",Space,Str "pleine",Space,Str "de",Space,Str "reves,",LineBreak,Str "Ou",Space,Str "le",Space,Str "spectre",Space,Str "en",Space,Str "plein",Space,Str "jour",Space,Str "raccroche",Space,Str "le",Space,Str "passant.\""]]]] [Plain [Str "Unreal",Space,Str "City,",Note [Para [Link ("",[],[]) [Str "60."] ("#wasteland-content.xhtml#ln60",""),Space,Str "Cf.",Space,Str "Baudelaire:"],BlockQuote [Para [Str "\"Fourmillante",Space,Str "cite;,",Space,Str "cite;",Space,Str "pleine",Space,Str "de",Space,Str "reves,",LineBreak,Str "Ou",Space,Str "le",Space,Str "spectre",Space,Str "en",Space,Str "plein",Space,Str "jour",Space,Str "raccroche",Space,Str "le",Space,Str "passant.\""]]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Under",Space,Str "the",Space,Str "brown",Space,Str "fog",Space,Str "of",Space,Str "a",Space,Str "winter",Space,Str "dawn,"]] [Plain [Str "Under",Space,Str "the",Space,Str "brown",Space,Str "fog",Space,Str "of",Space,Str "a",Space,Str "winter",Space,Str "dawn,"]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "A",Space,Str "crowd",Space,Str "flowed",Space,Str "over",Space,Str "London",Space,Str "Bridge,",Space,Str "so",Space,Str "many,"]] [Plain [Str "A",Space,Str "crowd",Space,Str "flowed",Space,Str "over",Space,Str "London",Space,Str "Bridge,",Space,Str "so",Space,Str "many,"]]
,Div ("wasteland-content.xhtml#ln63",[],[]) ,Div ("wasteland-content.xhtml#ln63",[],[])
[Plain [Str "I",Space,Str "had",Space,Str "not",Space,Str "thought",Space,Str "death",Space,Str "had",Space,Str "undone",Space,Str "so",Space,Str "many.",Note [Para [Link [Str "63."] ("#wasteland-content.xhtml#ln63",""),Space,Str "Cf.",Space,Str "Inferno,",Space,Str "iii.",Space,Str "55-7."],BlockQuote [Para [Str "\"si",Space,Str "lunga",Space,Str "tratta",LineBreak,Str "di",Space,Str "gente,",Space,Str "ch'io",Space,Str "non",Space,Str "avrei",Space,Str "mai",Space,Str "creduto",LineBreak,Str "che",Space,Str "morte",Space,Str "tanta",Space,Str "n'avesse",Space,Str "disfatta.\""]]]] [Plain [Str "I",Space,Str "had",Space,Str "not",Space,Str "thought",Space,Str "death",Space,Str "had",Space,Str "undone",Space,Str "so",Space,Str "many.",Note [Para [Link ("",[],[]) [Str "63."] ("#wasteland-content.xhtml#ln63",""),Space,Str "Cf.",Space,Str "Inferno,",Space,Str "iii.",Space,Str "55-7."],BlockQuote [Para [Str "\"si",Space,Str "lunga",Space,Str "tratta",LineBreak,Str "di",Space,Str "gente,",Space,Str "ch'io",Space,Str "non",Space,Str "avrei",Space,Str "mai",Space,Str "creduto",LineBreak,Str "che",Space,Str "morte",Space,Str "tanta",Space,Str "n'avesse",Space,Str "disfatta.\""]]]]
,Div ("wasteland-content.xhtml#ln64",[],[]) ,Div ("wasteland-content.xhtml#ln64",[],[])
[Plain [Str "Sighs,",Space,Str "short",Space,Str "and",Space,Str "infrequent,",Space,Str "were",Space,Str "exhaled,",Note [Para [Link [Str "64."] ("#wasteland-content.xhtml#ln64",""),Space,Str "Cf.",Space,Str "Inferno,",Space,Str "iv.",Space,Str "25-7:"],BlockQuote [Para [Str "\"Quivi,",Space,Str "secondo",Space,Str "che",Space,Str "per",Space,Str "ascoltahre,",LineBreak,Str "\"non",Space,Str "avea",Space,Str "pianto,",Space,Str "ma'",Space,Str "che",Space,Str "di",Space,Str "sospiri,",LineBreak,Str "\"che",Space,Str "l'aura",Space,Str "eterna",Space,Str "facevan",Space,Str "tremare.\""]]]] [Plain [Str "Sighs,",Space,Str "short",Space,Str "and",Space,Str "infrequent,",Space,Str "were",Space,Str "exhaled,",Note [Para [Link ("",[],[]) [Str "64."] ("#wasteland-content.xhtml#ln64",""),Space,Str "Cf.",Space,Str "Inferno,",Space,Str "iv.",Space,Str "25-7:"],BlockQuote [Para [Str "\"Quivi,",Space,Str "secondo",Space,Str "che",Space,Str "per",Space,Str "ascoltahre,",LineBreak,Str "\"non",Space,Str "avea",Space,Str "pianto,",Space,Str "ma'",Space,Str "che",Space,Str "di",Space,Str "sospiri,",LineBreak,Str "\"che",Space,Str "l'aura",Space,Str "eterna",Space,Str "facevan",Space,Str "tremare.\""]]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "And",Space,Str "each",Space,Str "man",Space,Str "fixed",Space,Str "his",Space,Str "eyes",Space,Str "before",Space,Str "his",Space,Str "feet."]] [Plain [Str "And",Space,Str "each",Space,Str "man",Space,Str "fixed",Space,Str "his",Space,Str "eyes",Space,Str "before",Space,Str "his",Space,Str "feet."]]
,Div ("",[],[]) ,Div ("",[],[])
@ -147,7 +147,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "To",Space,Str "where",Space,Str "Saint",Space,Str "Mary",Space,Str "Woolnoth",Space,Str "kept",Space,Str "the",Space,Str "hours"]] [Plain [Str "To",Space,Str "where",Space,Str "Saint",Space,Str "Mary",Space,Str "Woolnoth",Space,Str "kept",Space,Str "the",Space,Str "hours"]]
,Div ("wasteland-content.xhtml#ln68",[],[]) ,Div ("wasteland-content.xhtml#ln68",[],[])
[Plain [Str "With",Space,Str "a",Space,Str "dead",Space,Str "sound",Space,Str "on",Space,Str "the",Space,Str "final",Space,Str "stroke",Space,Str "of",Space,Str "nine.",Note [Para [Link [Str "68."] ("#wasteland-content.xhtml#ln68",""),Space,Str "A",Space,Str "phenomenon",Space,Str "which",Space,Str "I",Space,Str "have",Space,Str "often",Space,Str "noticed."]]] [Plain [Str "With",Space,Str "a",Space,Str "dead",Space,Str "sound",Space,Str "on",Space,Str "the",Space,Str "final",Space,Str "stroke",Space,Str "of",Space,Str "nine.",Note [Para [Link ("",[],[]) [Str "68."] ("#wasteland-content.xhtml#ln68",""),Space,Str "A",Space,Str "phenomenon",Space,Str "which",Space,Str "I",Space,Str "have",Space,Str "often",Space,Str "noticed."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "There",Space,Str "I",Space,Str "saw",Space,Str "one",Space,Str "I",Space,Str "knew,",Space,Str "and",Space,Str "stopped",Space,Str "him,",Space,Str "crying",Space,Str "\"Stetson!"]] [Plain [Str "There",Space,Str "I",Space,Str "saw",Space,Str "one",Space,Str "I",Space,Str "knew,",Space,Str "and",Space,Str "stopped",Space,Str "him,",Space,Str "crying",Space,Str "\"Stetson!"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -160,16 +160,16 @@
[Plain [Str "\"Or",Space,Str "has",Space,Str "the",Space,Str "sudden",Space,Str "frost",Space,Str "disturbed",Space,Str "its",Space,Str "bed?"]]] [Plain [Str "\"Or",Space,Str "has",Space,Str "the",Space,Str "sudden",Space,Str "frost",Space,Str "disturbed",Space,Str "its",Space,Str "bed?"]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("wasteland-content.xhtml#ln74",[],[]) [Div ("wasteland-content.xhtml#ln74",[],[])
[Plain [Str "\"Oh",Space,Str "keep",Space,Str "the",Space,Str "Dog",Space,Str "far",Space,Str "hence,",Space,Str "that's",Space,Str "friend",Space,Str "to",Space,Str "men,",Note [Para [Link [Str "74."] ("#wasteland-content.xhtml#ln74",""),Space,Str "Cf.",Space,Str "the",Space,Str "Dirge",Space,Str "in",Space,Str "Webster's",Space,Str "White",Space,Str "Devil",Space,Str "."]]] [Plain [Str "\"Oh",Space,Str "keep",Space,Str "the",Space,Str "Dog",Space,Str "far",Space,Str "hence,",Space,Str "that's",Space,Str "friend",Space,Str "to",Space,Str "men,",Note [Para [Link ("",[],[]) [Str "74."] ("#wasteland-content.xhtml#ln74",""),Space,Str "Cf.",Space,Str "the",Space,Str "Dirge",Space,Str "in",Space,Str "Webster's",Space,Str "White",Space,Str "Devil",Space,Str "."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "\"Or",Space,Str "with",Space,Str "his",Space,Str "nails",Space,Str "he'll",Space,Str "dig",Space,Str "it",Space,Str "up",Space,Str "again!"]] [Plain [Str "\"Or",Space,Str "with",Space,Str "his",Space,Str "nails",Space,Str "he'll",Space,Str "dig",Space,Str "it",Space,Str "up",Space,Str "again!"]]
,Div ("wasteland-content.xhtml#ln76",[],[]) ,Div ("wasteland-content.xhtml#ln76",[],[])
[Plain [Str "\"You!",Space,Span ("",[],[("lang","fr")]) [Str "hypocrite",Space,Str "lecteur!",Space,Str "-",Space,Str "mon",Space,Str "semblable,",Space,Str "-",Space,Str "mon",Space,Str "frere"],Space,Str "!\"",Note [Para [Link [Str "76."] ("#wasteland-content.xhtml#ln76",""),Space,Str "V.",Space,Str "Baudelaire,",Space,Str "Preface",Space,Str "to",Space,Str "Fleurs",Space,Str "du",Space,Str "Mal."]]] [Plain [Str "\"You!",Space,Span ("",[],[("lang","fr")]) [Str "hypocrite",Space,Str "lecteur!",Space,Str "-",Space,Str "mon",Space,Str "semblable,",Space,Str "-",Space,Str "mon",Space,Str "frere"],Space,Str "!\"",Note [Para [Link ("",[],[]) [Str "76."] ("#wasteland-content.xhtml#ln76",""),Space,Str "V.",Space,Str "Baudelaire,",Space,Str "Preface",Space,Str "to",Space,Str "Fleurs",Space,Str "du",Space,Str "Mal."]]]
,Div ("wasteland-content.xhtml#ch2",["section"],[]) ,Div ("wasteland-content.xhtml#ch2",["section"],[])
[Header 2 ("",[],[]) [Str "II.",Space,Str "A",Space,Str "GAME",Space,Str "OF",Space,Str "CHESS"] [Header 2 ("",[],[]) [Str "II.",Space,Str "A",Space,Str "GAME",Space,Str "OF",Space,Str "CHESS"]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("wasteland-content.xhtml#ln77",[],[]) [Div ("wasteland-content.xhtml#ln77",[],[])
[Plain [Str "The",Space,Str "Chair",Space,Str "she",Space,Str "sat",Space,Str "in,",Space,Str "like",Space,Str "a",Space,Str "burnished",Space,Str "throne,",Note [Para [Link [Str "77."] ("#wasteland-content.xhtml#ln77",""),Space,Str "Cf.",Space,Str "Antony",Space,Str "and",Space,Str "Cleopatra,",Space,Str "II.",Space,Str "ii.,",Space,Str "l.",Space,Str "190."]]] [Plain [Str "The",Space,Str "Chair",Space,Str "she",Space,Str "sat",Space,Str "in,",Space,Str "like",Space,Str "a",Space,Str "burnished",Space,Str "throne,",Note [Para [Link ("",[],[]) [Str "77."] ("#wasteland-content.xhtml#ln77",""),Space,Str "Cf.",Space,Str "Antony",Space,Str "and",Space,Str "Cleopatra,",Space,Str "II.",Space,Str "ii.,",Space,Str "l.",Space,Str "190."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Glowed",Space,Str "on",Space,Str "the",Space,Str "marble,",Space,Str "where",Space,Str "the",Space,Str "glass"]] [Plain [Str "Glowed",Space,Str "on",Space,Str "the",Space,Str "marble,",Space,Str "where",Space,Str "the",Space,Str "glass"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -199,7 +199,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "In",Space,Str "fattening",Space,Str "the",Space,Str "prolonged",Space,Str "candle-flames,"]] [Plain [Str "In",Space,Str "fattening",Space,Str "the",Space,Str "prolonged",Space,Str "candle-flames,"]]
,Div ("wasteland-content.xhtml#ln92",[],[]) ,Div ("wasteland-content.xhtml#ln92",[],[])
[Plain [Str "Flung",Space,Str "their",Space,Str "smoke",Space,Str "into",Space,Str "the",Space,Str "laquearia,",Note [Para [Link [Str "92."] ("#wasteland-content.xhtml#ln92",""),Space,Str "Laquearia.",Space,Str "V.",Space,Str "Aeneid,",Space,Str "I.",Space,Str "726:"],BlockQuote [Para [Str "dependent",Space,Str "lychni",Space,Str "laquearibus",Space,Str "aureis",Space,Str "incensi,",Space,Str "et",Space,Str "noctem",Space,Str "flammis",LineBreak,Str "funalia",Space,Str "vincunt."]]]] [Plain [Str "Flung",Space,Str "their",Space,Str "smoke",Space,Str "into",Space,Str "the",Space,Str "laquearia,",Note [Para [Link ("",[],[]) [Str "92."] ("#wasteland-content.xhtml#ln92",""),Space,Str "Laquearia.",Space,Str "V.",Space,Str "Aeneid,",Space,Str "I.",Space,Str "726:"],BlockQuote [Para [Str "dependent",Space,Str "lychni",Space,Str "laquearibus",Space,Str "aureis",Space,Str "incensi,",Space,Str "et",Space,Str "noctem",Space,Str "flammis",LineBreak,Str "funalia",Space,Str "vincunt."]]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Stirring",Space,Str "the",Space,Str "pattern",Space,Str "on",Space,Str "the",Space,Str "coffered",Space,Str "ceiling."]] [Plain [Str "Stirring",Space,Str "the",Space,Str "pattern",Space,Str "on",Space,Str "the",Space,Str "coffered",Space,Str "ceiling."]]
,Div ("",[],[]) ,Div ("",[],[])
@ -211,11 +211,11 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Above",Space,Str "the",Space,Str "antique",Space,Str "mantel",Space,Str "was",Space,Str "displayed"]] [Plain [Str "Above",Space,Str "the",Space,Str "antique",Space,Str "mantel",Space,Str "was",Space,Str "displayed"]]
,Div ("wasteland-content.xhtml#ln98",[],[]) ,Div ("wasteland-content.xhtml#ln98",[],[])
[Plain [Str "As",Space,Str "though",Space,Str "a",Space,Str "window",Space,Str "gave",Space,Str "upon",Space,Str "the",Space,Str "sylvan",Space,Str "scene",Note [Para [Link [Str "98."] ("#wasteland-content.xhtml#ln98",""),Space,Str "Sylvan",Space,Str "scene.",Space,Str "V.",Space,Str "Milton,",Space,Str "Paradise",Space,Str "Lost,",Space,Str "iv.",Space,Str "140."]]] [Plain [Str "As",Space,Str "though",Space,Str "a",Space,Str "window",Space,Str "gave",Space,Str "upon",Space,Str "the",Space,Str "sylvan",Space,Str "scene",Note [Para [Link ("",[],[]) [Str "98."] ("#wasteland-content.xhtml#ln98",""),Space,Str "Sylvan",Space,Str "scene.",Space,Str "V.",Space,Str "Milton,",Space,Str "Paradise",Space,Str "Lost,",Space,Str "iv.",Space,Str "140."]]]
,Div ("wasteland-content.xhtml#ln99",[],[]) ,Div ("wasteland-content.xhtml#ln99",[],[])
[Plain [Str "The",Space,Str "change",Space,Str "of",Space,Str "Philomel,",Space,Str "by",Space,Str "the",Space,Str "barbarous",Space,Str "king",Note [Para [Link [Str "99."] ("#wasteland-content.xhtml#ln99",""),Space,Str "V.",Space,Str "Ovid,",Space,Str "Metamorphoses,",Space,Str "vi,",Space,Str "Philomela."]]] [Plain [Str "The",Space,Str "change",Space,Str "of",Space,Str "Philomel,",Space,Str "by",Space,Str "the",Space,Str "barbarous",Space,Str "king",Note [Para [Link ("",[],[]) [Str "99."] ("#wasteland-content.xhtml#ln99",""),Space,Str "V.",Space,Str "Ovid,",Space,Str "Metamorphoses,",Space,Str "vi,",Space,Str "Philomela."]]]
,Div ("wasteland-content.xhtml#ln100",[],[]) ,Div ("wasteland-content.xhtml#ln100",[],[])
[Plain [Str "So",Space,Str "rudely",Space,Str "forced;",Space,Str "yet",Space,Str "there",Space,Str "the",Space,Str "nightingale",Note [Para [Link [Str "100."] ("#wasteland-content.xhtml#ln100",""),Space,Str "Cf.",Space,Str "Part",Space,Str "III,",Space,Str "l.",Space,Str "204."]]] [Plain [Str "So",Space,Str "rudely",Space,Str "forced;",Space,Str "yet",Space,Str "there",Space,Str "the",Space,Str "nightingale",Note [Para [Link ("",[],[]) [Str "100."] ("#wasteland-content.xhtml#ln100",""),Space,Str "Cf.",Space,Str "Part",Space,Str "III,",Space,Str "l.",Space,Str "204."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Filled",Space,Str "all",Space,Str "the",Space,Str "desert",Space,Str "with",Space,Str "inviolable",Space,Str "voice"]] [Plain [Str "Filled",Space,Str "all",Space,Str "the",Space,Str "desert",Space,Str "with",Space,Str "inviolable",Space,Str "voice"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -248,14 +248,14 @@
[Plain [Str "\"I",Space,Str "never",Space,Str "know",Space,Str "what",Space,Str "you",Space,Str "are",Space,Str "thinking.",Space,Str "Think.\""]]] [Plain [Str "\"I",Space,Str "never",Space,Str "know",Space,Str "what",Space,Str "you",Space,Str "are",Space,Str "thinking.",Space,Str "Think.\""]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("wasteland-content.xhtml#ln115",[],[]) [Div ("wasteland-content.xhtml#ln115",[],[])
[Plain [Str "I",Space,Str "think",Space,Str "we",Space,Str "are",Space,Str "in",Space,Str "rats'",Space,Str "alley",Note [Para [Link [Str "115."] ("#wasteland-content.xhtml#ln115",""),Space,Str "Cf.",Space,Str "Part",Space,Str "III,",Space,Str "l.",Space,Str "195."]]] [Plain [Str "I",Space,Str "think",Space,Str "we",Space,Str "are",Space,Str "in",Space,Str "rats'",Space,Str "alley",Note [Para [Link ("",[],[]) [Str "115."] ("#wasteland-content.xhtml#ln115",""),Space,Str "Cf.",Space,Str "Part",Space,Str "III,",Space,Str "l.",Space,Str "195."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Where",Space,Str "the",Space,Str "dead",Space,Str "men",Space,Str "lost",Space,Str "their",Space,Str "bones."]]]] [Plain [Str "Where",Space,Str "the",Space,Str "dead",Space,Str "men",Space,Str "lost",Space,Str "their",Space,Str "bones."]]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("",[],[]) [Div ("",[],[])
[Plain [Str "\"What",Space,Str "is",Space,Str "that",Space,Str "noise?\""]] [Plain [Str "\"What",Space,Str "is",Space,Str "that",Space,Str "noise?\""]]
,Div ("wasteland-content.xhtml#ln118",["indent"],[]) ,Div ("wasteland-content.xhtml#ln118",["indent"],[])
[Plain [Str "The",Space,Str "wind",Space,Str "under",Space,Str "the",Space,Str "door.",Note [Para [Link [Str "118."] ("#wasteland-content.xhtml#ln118",""),Space,Str "Cf.",Space,Str "Webster:"],BlockQuote [Para [Str "\"Is",Space,Str "the",Space,Str "wind",Space,Str "in",Space,Str "that",Space,Str "door",Space,Str "still?\""]]]] [Plain [Str "The",Space,Str "wind",Space,Str "under",Space,Str "the",Space,Str "door.",Note [Para [Link ("",[],[]) [Str "118."] ("#wasteland-content.xhtml#ln118",""),Space,Str "Cf.",Space,Str "Webster:"],BlockQuote [Para [Str "\"Is",Space,Str "the",Space,Str "wind",Space,Str "in",Space,Str "that",Space,Str "door",Space,Str "still?\""]]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "\"What",Space,Str "is",Space,Str "that",Space,Str "noise",Space,Str "now?",Space,Str "What",Space,Str "is",Space,Str "the",Space,Str "wind",Space,Str "doing?\""]] [Plain [Str "\"What",Space,Str "is",Space,Str "that",Space,Str "noise",Space,Str "now?",Space,Str "What",Space,Str "is",Space,Str "the",Space,Str "wind",Space,Str "doing?\""]]
,Div ("",["indent"],[]) ,Div ("",["indent"],[])
@ -273,7 +273,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Those",Space,Str "are",Space,Str "pearls",Space,Str "that",Space,Str "were",Space,Str "his",Space,Str "eyes."]] [Plain [Str "Those",Space,Str "are",Space,Str "pearls",Space,Str "that",Space,Str "were",Space,Str "his",Space,Str "eyes."]]
,Div ("wasteland-content.xhtml#ln126",[],[]) ,Div ("wasteland-content.xhtml#ln126",[],[])
[Plain [Str "\"Are",Space,Str "you",Space,Str "alive,",Space,Str "or",Space,Str "not?",Space,Str "Is",Space,Str "there",Space,Str "nothing",Space,Str "in",Space,Str "your",Space,Str "head?\"",Note [Para [Link [Str "126."] ("#wasteland-content.xhtml#ln126",""),Space,Str "Cf.",Space,Str "Part",Space,Str "I,",Space,Str "l.",Space,Str "37,",Space,Str "48."]]] [Plain [Str "\"Are",Space,Str "you",Space,Str "alive,",Space,Str "or",Space,Str "not?",Space,Str "Is",Space,Str "there",Space,Str "nothing",Space,Str "in",Space,Str "your",Space,Str "head?\"",Note [Para [Link ("",[],[]) [Str "126."] ("#wasteland-content.xhtml#ln126",""),Space,Str "Cf.",Space,Str "Part",Space,Str "I,",Space,Str "l.",Space,Str "37,",Space,Str "48."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "But"]] [Plain [Str "But"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -297,7 +297,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "And",Space,Str "we",Space,Str "shall",Space,Str "play",Space,Str "a",Space,Str "game",Space,Str "of",Space,Str "chess,"]] [Plain [Str "And",Space,Str "we",Space,Str "shall",Space,Str "play",Space,Str "a",Space,Str "game",Space,Str "of",Space,Str "chess,"]]
,Div ("wasteland-content.xhtml#ln138",[],[]) ,Div ("wasteland-content.xhtml#ln138",[],[])
[Plain [Str "Pressing",Space,Str "lidless",Space,Str "eyes",Space,Str "and",Space,Str "waiting",Space,Str "for",Space,Str "a",Space,Str "knock",Space,Str "upon",Space,Str "the",Space,Str "door.",Note [Para [Link [Str "138."] ("#wasteland-content.xhtml#ln138",""),Space,Str "Cf.",Space,Str "the",Space,Str "game",Space,Str "of",Space,Str "chess",Space,Str "in",Space,Str "Middleton's",Space,Str "Women",Space,Str "beware",Space,Str "Women."]]] [Plain [Str "Pressing",Space,Str "lidless",Space,Str "eyes",Space,Str "and",Space,Str "waiting",Space,Str "for",Space,Str "a",Space,Str "knock",Space,Str "upon",Space,Str "the",Space,Str "door.",Note [Para [Link ("",[],[]) [Str "138."] ("#wasteland-content.xhtml#ln138",""),Space,Str "Cf.",Space,Str "the",Space,Str "game",Space,Str "of",Space,Str "chess",Space,Str "in",Space,Str "Middleton's",Space,Str "Women",Space,Str "beware",Space,Str "Women."]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("",[],[]) [Div ("",[],[])
[Plain [Str "When",Space,Str "Lil's",Space,Str "husband",Space,Str "got",Space,Str "demobbed,",Space,Str "I",Space,Str "said",Space,Str "-"]] [Plain [Str "When",Space,Str "Lil's",Space,Str "husband",Space,Str "got",Space,Str "demobbed,",Space,Str "I",Space,Str "said",Space,Str "-"]]
@ -378,7 +378,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Crosses",Space,Str "the",Space,Str "brown",Space,Str "land,",Space,Str "unheard.",Space,Str "The",Space,Str "nymphs",Space,Str "are",Space,Str "departed."]] [Plain [Str "Crosses",Space,Str "the",Space,Str "brown",Space,Str "land,",Space,Str "unheard.",Space,Str "The",Space,Str "nymphs",Space,Str "are",Space,Str "departed."]]
,Div ("wasteland-content.xhtml#ln176",[],[]) ,Div ("wasteland-content.xhtml#ln176",[],[])
[Plain [Str "Sweet",Space,Str "Thames,",Space,Str "run",Space,Str "softly,",Space,Str "till",Space,Str "I",Space,Str "end",Space,Str "my",Space,Str "song.",Note [Para [Link [Str "176."] ("#wasteland-content.xhtml#ln176",""),Space,Str "V.",Space,Str "Spenser,",Space,Str "Prothalamion."]]] [Plain [Str "Sweet",Space,Str "Thames,",Space,Str "run",Space,Str "softly,",Space,Str "till",Space,Str "I",Space,Str "end",Space,Str "my",Space,Str "song.",Note [Para [Link ("",[],[]) [Str "176."] ("#wasteland-content.xhtml#ln176",""),Space,Str "V.",Space,Str "Spenser,",Space,Str "Prothalamion."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "The",Space,Str "river",Space,Str "bears",Space,Str "no",Space,Str "empty",Space,Str "bottles,",Space,Str "sandwich",Space,Str "papers,"]] [Plain [Str "The",Space,Str "river",Space,Str "bears",Space,Str "no",Space,Str "empty",Space,Str "bottles,",Space,Str "sandwich",Space,Str "papers,"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -411,7 +411,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Musing",Space,Str "upon",Space,Str "the",Space,Str "king",Space,Str "my",Space,Str "brother's",Space,Str "wreck"]] [Plain [Str "Musing",Space,Str "upon",Space,Str "the",Space,Str "king",Space,Str "my",Space,Str "brother's",Space,Str "wreck"]]
,Div ("wasteland-content.xhtml#ln192",[],[]) ,Div ("wasteland-content.xhtml#ln192",[],[])
[Plain [Str "And",Space,Str "on",Space,Str "the",Space,Str "king",Space,Str "my",Space,Str "father's",Space,Str "death",Space,Str "before",Space,Str "him.",Note [Para [Link [Str "192."] ("#wasteland-content.xhtml#ln192",""),Space,Str "Cf.",Space,Str "The",Space,Str "Tempest,",Space,Str "I.",Space,Str "ii."]]] [Plain [Str "And",Space,Str "on",Space,Str "the",Space,Str "king",Space,Str "my",Space,Str "father's",Space,Str "death",Space,Str "before",Space,Str "him.",Note [Para [Link ("",[],[]) [Str "192."] ("#wasteland-content.xhtml#ln192",""),Space,Str "Cf.",Space,Str "The",Space,Str "Tempest,",Space,Str "I.",Space,Str "ii."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "White",Space,Str "bodies",Space,Str "naked",Space,Str "on",Space,Str "the",Space,Str "low",Space,Str "damp",Space,Str "ground"]] [Plain [Str "White",Space,Str "bodies",Space,Str "naked",Space,Str "on",Space,Str "the",Space,Str "low",Space,Str "damp",Space,Str "ground"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -419,19 +419,19 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Rattled",Space,Str "by",Space,Str "the",Space,Str "rat's",Space,Str "foot",Space,Str "only,",Space,Str "year",Space,Str "to",Space,Str "year."]] [Plain [Str "Rattled",Space,Str "by",Space,Str "the",Space,Str "rat's",Space,Str "foot",Space,Str "only,",Space,Str "year",Space,Str "to",Space,Str "year."]]
,Div ("wasteland-content.xhtml#ln196",[],[]) ,Div ("wasteland-content.xhtml#ln196",[],[])
[Plain [Str "But",Space,Str "at",Space,Str "my",Space,Str "back",Space,Str "from",Space,Str "time",Space,Str "to",Space,Str "time",Space,Str "I",Space,Str "hear",Note [Para [Link [Str "196."] ("#wasteland-content.xhtml#ln196",""),Space,Str "Cf.",Space,Str "Marvell,",Space,Str "To",Space,Str "His",Space,Str "Coy",Space,Str "Mistress."]]] [Plain [Str "But",Space,Str "at",Space,Str "my",Space,Str "back",Space,Str "from",Space,Str "time",Space,Str "to",Space,Str "time",Space,Str "I",Space,Str "hear",Note [Para [Link ("",[],[]) [Str "196."] ("#wasteland-content.xhtml#ln196",""),Space,Str "Cf.",Space,Str "Marvell,",Space,Str "To",Space,Str "His",Space,Str "Coy",Space,Str "Mistress."]]]
,Div ("wasteland-content.xhtml#ln197",[],[]) ,Div ("wasteland-content.xhtml#ln197",[],[])
[Plain [Str "The",Space,Str "sound",Space,Str "of",Space,Str "horns",Space,Str "and",Space,Str "motors,",Space,Str "which",Space,Str "shall",Space,Str "bring",Note [Para [Link [Str "197."] ("#wasteland-content.xhtml#ln197",""),Space,Str "Cf.",Space,Str "Day,",Space,Str "Parliament",Space,Str "of",Space,Str "Bees:"],BlockQuote [Div ("",[],[]) [Div ("",[],[]) [Plain [Str "\"When",Space,Str "of",Space,Str "the",Space,Str "sudden,",Space,Str "listening,",Space,Str "you",Space,Str "shall",Space,Str "hear,"]],Div ("",[],[]) [Plain [Str "\"A",Space,Str "noise",Space,Str "of",Space,Str "horns",Space,Str "and",Space,Str "hunting,",Space,Str "which",Space,Str "shall",Space,Str "bring"]],Div ("",[],[]) [Plain [Str "\"Actaeon",Space,Str "to",Space,Str "Diana",Space,Str "in",Space,Str "the",Space,Str "spring,"]],Div ("",[],[]) [Plain [Str "\"Where",Space,Str "all",Space,Str "shall",Space,Str "see",Space,Str "her",Space,Str "naked",Space,Str "skin",Space,Str ".",Space,Str ".",Space,Str ".\""]]]]]] [Plain [Str "The",Space,Str "sound",Space,Str "of",Space,Str "horns",Space,Str "and",Space,Str "motors,",Space,Str "which",Space,Str "shall",Space,Str "bring",Note [Para [Link ("",[],[]) [Str "197."] ("#wasteland-content.xhtml#ln197",""),Space,Str "Cf.",Space,Str "Day,",Space,Str "Parliament",Space,Str "of",Space,Str "Bees:"],BlockQuote [Div ("",[],[]) [Div ("",[],[]) [Plain [Str "\"When",Space,Str "of",Space,Str "the",Space,Str "sudden,",Space,Str "listening,",Space,Str "you",Space,Str "shall",Space,Str "hear,"]],Div ("",[],[]) [Plain [Str "\"A",Space,Str "noise",Space,Str "of",Space,Str "horns",Space,Str "and",Space,Str "hunting,",Space,Str "which",Space,Str "shall",Space,Str "bring"]],Div ("",[],[]) [Plain [Str "\"Actaeon",Space,Str "to",Space,Str "Diana",Space,Str "in",Space,Str "the",Space,Str "spring,"]],Div ("",[],[]) [Plain [Str "\"Where",Space,Str "all",Space,Str "shall",Space,Str "see",Space,Str "her",Space,Str "naked",Space,Str "skin",Space,Str ".",Space,Str ".",Space,Str ".\""]]]]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Sweeney",Space,Str "to",Space,Str "Mrs.",Space,Str "Porter",Space,Str "in",Space,Str "the",Space,Str "spring."]] [Plain [Str "Sweeney",Space,Str "to",Space,Str "Mrs.",Space,Str "Porter",Space,Str "in",Space,Str "the",Space,Str "spring."]]
,Div ("wasteland-content.xhtml#ln199",[],[]) ,Div ("wasteland-content.xhtml#ln199",[],[])
[Plain [Str "O",Space,Str "the",Space,Str "moon",Space,Str "shone",Space,Str "bright",Space,Str "on",Space,Str "Mrs.",Space,Str "Porter",Note [Para [Link [Str "199."] ("#wasteland-content.xhtml#ln199",""),Space,Str "I",Space,Str "do",Space,Str "not",Space,Str "know",Space,Str "the",Space,Str "origin",Space,Str "of",Space,Str "the",Space,Str "ballad",Space,Str "from",Space,Str "which",Space,Str "these",Space,Str "lines",Space,Str "are",Space,Str "taken:",Space,Str "it",Space,Str "was",Space,Str "reported",Space,Str "to",Space,Str "me",Space,Str "from",Space,Str "Sydney,",Space,Str "Australia."]]] [Plain [Str "O",Space,Str "the",Space,Str "moon",Space,Str "shone",Space,Str "bright",Space,Str "on",Space,Str "Mrs.",Space,Str "Porter",Note [Para [Link ("",[],[]) [Str "199."] ("#wasteland-content.xhtml#ln199",""),Space,Str "I",Space,Str "do",Space,Str "not",Space,Str "know",Space,Str "the",Space,Str "origin",Space,Str "of",Space,Str "the",Space,Str "ballad",Space,Str "from",Space,Str "which",Space,Str "these",Space,Str "lines",Space,Str "are",Space,Str "taken:",Space,Str "it",Space,Str "was",Space,Str "reported",Space,Str "to",Space,Str "me",Space,Str "from",Space,Str "Sydney,",Space,Str "Australia."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "And",Space,Str "on",Space,Str "her",Space,Str "daughter",Span ("",["lnum"],[]) [Str "200"]]] [Plain [Str "And",Space,Str "on",Space,Str "her",Space,Str "daughter",Span ("",["lnum"],[]) [Str "200"]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "They",Space,Str "wash",Space,Str "their",Space,Str "feet",Space,Str "in",Space,Str "soda",Space,Str "water"]] [Plain [Str "They",Space,Str "wash",Space,Str "their",Space,Str "feet",Space,Str "in",Space,Str "soda",Space,Str "water"]]
,Div ("wasteland-content.xhtml#ln202",[],[("lang","fr")]) ,Div ("wasteland-content.xhtml#ln202",[],[("lang","fr")])
[Plain [Emph [Str "Et",Space,Str "O",Space,Str "ces",Space,Str "voix",Space,Str "d'enfants,",Space,Str "chantant",Space,Str "dans",Space,Str "la",Space,Str "coupole"],Str "!",Note [Para [Link [Str "202."] ("#wasteland-content.xhtml#ln202",""),Space,Str "V.",Space,Str "Verlaine,",Space,Str "Parsifal."]]] [Plain [Emph [Str "Et",Space,Str "O",Space,Str "ces",Space,Str "voix",Space,Str "d'enfants,",Space,Str "chantant",Space,Str "dans",Space,Str "la",Space,Str "coupole"],Str "!",Note [Para [Link ("",[],[]) [Str "202."] ("#wasteland-content.xhtml#ln202",""),Space,Str "V.",Space,Str "Verlaine,",Space,Str "Parsifal."]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("",[],[]) [Div ("",[],[])
[Plain [Str "Twit",Space,Str "twit",Space,Str "twit"]] [Plain [Str "Twit",Space,Str "twit",Space,Str "twit"]]
@ -449,7 +449,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Mr.",Space,Str "Eugenides,",Space,Str "the",Space,Str "Smyrna",Space,Str "merchant"]] [Plain [Str "Mr.",Space,Str "Eugenides,",Space,Str "the",Space,Str "Smyrna",Space,Str "merchant"]]
,Div ("wasteland-content.xhtml#ln210",[],[]) ,Div ("wasteland-content.xhtml#ln210",[],[])
[Plain [Str "Unshaven,",Space,Str "with",Space,Str "a",Space,Str "pocket",Space,Str "full",Space,Str "of",Space,Str "currants",Note [Para [Link [Str "210."] ("#wasteland-content.xhtml#ln210",""),Space,Str "The",Space,Str "currants",Space,Str "were",Space,Str "quoted",Space,Str "at",Space,Str "a",Space,Str "price",Space,Str "\"cost",Space,Str "insurance",Space,Str "and",Space,Str "freight",Space,Str "to",Space,Str "London\";",Space,Str "and",Space,Str "the",Space,Str "Bill",Space,Str "of",Space,Str "Lading",Space,Str "etc.",Space,Str "were",Space,Str "to",Space,Str "be",Space,Str "handed",Space,Str "to",Space,Str "the",Space,Str "buyer",Space,Str "upon",Space,Str "payment",Space,Str "of",Space,Str "the",Space,Str "sight",Space,Str "draft."]]] [Plain [Str "Unshaven,",Space,Str "with",Space,Str "a",Space,Str "pocket",Space,Str "full",Space,Str "of",Space,Str "currants",Note [Para [Link ("",[],[]) [Str "210."] ("#wasteland-content.xhtml#ln210",""),Space,Str "The",Space,Str "currants",Space,Str "were",Space,Str "quoted",Space,Str "at",Space,Str "a",Space,Str "price",Space,Str "\"cost",Space,Str "insurance",Space,Str "and",Space,Str "freight",Space,Str "to",Space,Str "London\";",Space,Str "and",Space,Str "the",Space,Str "Bill",Space,Str "of",Space,Str "Lading",Space,Str "etc.",Space,Str "were",Space,Str "to",Space,Str "be",Space,Str "handed",Space,Str "to",Space,Str "the",Space,Str "buyer",Space,Str "upon",Space,Str "payment",Space,Str "of",Space,Str "the",Space,Str "sight",Space,Str "draft."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "C.i.f.",Space,Str "London:",Space,Str "documents",Space,Str "at",Space,Str "sight,"]] [Plain [Str "C.i.f.",Space,Str "London:",Space,Str "documents",Space,Str "at",Space,Str "sight,"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -466,13 +466,13 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Like",Space,Str "a",Space,Str "taxi",Space,Str "throbbing",Space,Str "waiting,"]] [Plain [Str "Like",Space,Str "a",Space,Str "taxi",Space,Str "throbbing",Space,Str "waiting,"]]
,Div ("wasteland-content.xhtml#ln218",[],[]) ,Div ("wasteland-content.xhtml#ln218",[],[])
[Plain [Str "I",Space,Str "Tiresias,",Space,Str "though",Space,Str "blind,",Space,Str "throbbing",Space,Str "between",Space,Str "two",Space,Str "lives,",Note [Para [Link [Str "218."] ("#wasteland-content.xhtml#ln218",""),Space,Str "Tiresias,",Space,Str "although",Space,Str "a",Space,Str "mere",Space,Str "spectator",Space,Str "and",Space,Str "not",Space,Str "indeed",Space,Str "a",Space,Str "\"character,\"",Space,Str "is",Space,Str "yet",Space,Str "the",Space,Str "most",Space,Str "important",Space,Str "personage",Space,Str "in",Space,Str "the",Space,Str "poem,",Space,Str "uniting",Space,Str "all",Space,Str "the",Space,Str "rest.",Space,Str "Just",Space,Str "as",Space,Str "the",Space,Str "one-eyed",Space,Str "merchant,",Space,Str "seller",Space,Str "of",Space,Str "currants,",Space,Str "melts",Space,Str "into",Space,Str "the",Space,Str "Phoenician",Space,Str "Sailor,",Space,Str "and",Space,Str "the",Space,Str "latter",Space,Str "is",Space,Str "not",Space,Str "wholly",Space,Str "distinct",Space,Str "from",Space,Str "Ferdinand",Space,Str "Prince",Space,Str "of",Space,Str "Naples,",Space,Str "so",Space,Str "all",Space,Str "the",Space,Str "women",Space,Str "are",Space,Str "one",Space,Str "woman,",Space,Str "and",Space,Str "the",Space,Str "two",Space,Str "sexes",Space,Str "meet",Space,Str "in",Space,Str "Tiresias.",Space,Str "What",Space,Str "Tiresias",Space,Str "sees,",Space,Str "in",Space,Str "fact,",Space,Str "is",Space,Str "the",Space,Str "substance",Space,Str "of",Space,Str "the",Space,Str "poem.",Space,Str "The",Space,Str "whole",Space,Str "passage",Space,Str "from",Space,Str "Ovid",Space,Str "is",Space,Str "of",Space,Str "great",Space,Str "anthropological",Space,Str "interest:"],BlockQuote [Para [Str "'.",Space,Str ".",Space,Str ".",Space,Str "Cum",Space,Str "Iunone",Space,Str "iocos",Space,Str "et",Space,Str "maior",Space,Str "vestra",Space,Str "profecto",Space,Str "est",LineBreak,Space,Str "Quam,",Space,Str "quae",Space,Str "contingit",Space,Str "maribus,'",Space,Str "dixisse,",Space,Str "'voluptas.'",LineBreak,Space,Str "Illa",Space,Str "negat;",Space,Str "placuit",Space,Str "quae",Space,Str "sit",Space,Str "sententia",Space,Str "docti",LineBreak,Space,Str "Quaerere",Space,Str "Tiresiae:",Space,Str "venus",Space,Str "huic",Space,Str "erat",Space,Str "utraque",Space,Str "nota.",LineBreak,Space,Str "Nam",Space,Str "duo",Space,Str "magnorum",Space,Str "viridi",Space,Str "coeuntia",Space,Str "silva",LineBreak,Space,Str "Corpora",Space,Str "serpentum",Space,Str "baculi",Space,Str "violaverat",Space,Str "ictu",LineBreak,Space,Str "Deque",Space,Str "viro",Space,Str "factus,",Space,Str "mirabile,",Space,Str "femina",Space,Str "septem",LineBreak,Space,Str "Egerat",Space,Str "autumnos;",Space,Str "octavo",Space,Str "rursus",Space,Str "eosdem",LineBreak,Space,Str "Vidit",Space,Str "et",Space,Str "'est",Space,Str "vestrae",Space,Str "si",Space,Str "tanta",Space,Str "potentia",Space,Str "plagae,'",LineBreak,Space,Str "Dixit",Space,Str "'ut",Space,Str "auctoris",Space,Str "sortem",Space,Str "in",Space,Str "contraria",Space,Str "mutet,",LineBreak,Space,Str "Nunc",Space,Str "quoque",Space,Str "vos",Space,Str "feriam!'",Space,Str "percussis",Space,Str "anguibus",Space,Str "isdem",LineBreak,Space,Str "Forma",Space,Str "prior",Space,Str "rediit",Space,Str "genetivaque",Space,Str "venit",Space,Str "imago.",LineBreak,Space,Str "Arbiter",Space,Str "hic",Space,Str "igitur",Space,Str "sumptus",Space,Str "de",Space,Str "lite",Space,Str "iocosa",LineBreak,Space,Str "Dicta",Space,Str "Iovis",Space,Str "firmat;",Space,Str "gravius",Space,Str "Saturnia",Space,Str "iusto",LineBreak,Space,Str "Nec",Space,Str "pro",Space,Str "materia",Space,Str "fertur",Space,Str "doluisse",Space,Str "suique",LineBreak,Space,Str "Iudicis",Space,Str "aeterna",Space,Str "damnavit",Space,Str "lumina",Space,Str "nocte,",LineBreak,Space,Str "At",Space,Str "pater",Space,Str "omnipotens",Space,Str "(neque",Space,Str "enim",Space,Str "licet",Space,Str "inrita",Space,Str "cuiquam",LineBreak,Space,Str "Facta",Space,Str "dei",Space,Str "fecisse",Space,Str "deo)",Space,Str "pro",Space,Str "lumine",Space,Str "adempto",LineBreak,Space,Str "Scire",Space,Str "futura",Space,Str "dedit",Space,Str "poenamque",Space,Str "levavit",Space,Str "honore.",LineBreak]]]] [Plain [Str "I",Space,Str "Tiresias,",Space,Str "though",Space,Str "blind,",Space,Str "throbbing",Space,Str "between",Space,Str "two",Space,Str "lives,",Note [Para [Link ("",[],[]) [Str "218."] ("#wasteland-content.xhtml#ln218",""),Space,Str "Tiresias,",Space,Str "although",Space,Str "a",Space,Str "mere",Space,Str "spectator",Space,Str "and",Space,Str "not",Space,Str "indeed",Space,Str "a",Space,Str "\"character,\"",Space,Str "is",Space,Str "yet",Space,Str "the",Space,Str "most",Space,Str "important",Space,Str "personage",Space,Str "in",Space,Str "the",Space,Str "poem,",Space,Str "uniting",Space,Str "all",Space,Str "the",Space,Str "rest.",Space,Str "Just",Space,Str "as",Space,Str "the",Space,Str "one-eyed",Space,Str "merchant,",Space,Str "seller",Space,Str "of",Space,Str "currants,",Space,Str "melts",Space,Str "into",Space,Str "the",Space,Str "Phoenician",Space,Str "Sailor,",Space,Str "and",Space,Str "the",Space,Str "latter",Space,Str "is",Space,Str "not",Space,Str "wholly",Space,Str "distinct",Space,Str "from",Space,Str "Ferdinand",Space,Str "Prince",Space,Str "of",Space,Str "Naples,",Space,Str "so",Space,Str "all",Space,Str "the",Space,Str "women",Space,Str "are",Space,Str "one",Space,Str "woman,",Space,Str "and",Space,Str "the",Space,Str "two",Space,Str "sexes",Space,Str "meet",Space,Str "in",Space,Str "Tiresias.",Space,Str "What",Space,Str "Tiresias",Space,Str "sees,",Space,Str "in",Space,Str "fact,",Space,Str "is",Space,Str "the",Space,Str "substance",Space,Str "of",Space,Str "the",Space,Str "poem.",Space,Str "The",Space,Str "whole",Space,Str "passage",Space,Str "from",Space,Str "Ovid",Space,Str "is",Space,Str "of",Space,Str "great",Space,Str "anthropological",Space,Str "interest:"],BlockQuote [Para [Str "'.",Space,Str ".",Space,Str ".",Space,Str "Cum",Space,Str "Iunone",Space,Str "iocos",Space,Str "et",Space,Str "maior",Space,Str "vestra",Space,Str "profecto",Space,Str "est",LineBreak,Space,Str "Quam,",Space,Str "quae",Space,Str "contingit",Space,Str "maribus,'",Space,Str "dixisse,",Space,Str "'voluptas.'",LineBreak,Space,Str "Illa",Space,Str "negat;",Space,Str "placuit",Space,Str "quae",Space,Str "sit",Space,Str "sententia",Space,Str "docti",LineBreak,Space,Str "Quaerere",Space,Str "Tiresiae:",Space,Str "venus",Space,Str "huic",Space,Str "erat",Space,Str "utraque",Space,Str "nota.",LineBreak,Space,Str "Nam",Space,Str "duo",Space,Str "magnorum",Space,Str "viridi",Space,Str "coeuntia",Space,Str "silva",LineBreak,Space,Str "Corpora",Space,Str "serpentum",Space,Str "baculi",Space,Str "violaverat",Space,Str "ictu",LineBreak,Space,Str "Deque",Space,Str "viro",Space,Str "factus,",Space,Str "mirabile,",Space,Str "femina",Space,Str "septem",LineBreak,Space,Str "Egerat",Space,Str "autumnos;",Space,Str "octavo",Space,Str "rursus",Space,Str "eosdem",LineBreak,Space,Str "Vidit",Space,Str "et",Space,Str "'est",Space,Str "vestrae",Space,Str "si",Space,Str "tanta",Space,Str "potentia",Space,Str "plagae,'",LineBreak,Space,Str "Dixit",Space,Str "'ut",Space,Str "auctoris",Space,Str "sortem",Space,Str "in",Space,Str "contraria",Space,Str "mutet,",LineBreak,Space,Str "Nunc",Space,Str "quoque",Space,Str "vos",Space,Str "feriam!'",Space,Str "percussis",Space,Str "anguibus",Space,Str "isdem",LineBreak,Space,Str "Forma",Space,Str "prior",Space,Str "rediit",Space,Str "genetivaque",Space,Str "venit",Space,Str "imago.",LineBreak,Space,Str "Arbiter",Space,Str "hic",Space,Str "igitur",Space,Str "sumptus",Space,Str "de",Space,Str "lite",Space,Str "iocosa",LineBreak,Space,Str "Dicta",Space,Str "Iovis",Space,Str "firmat;",Space,Str "gravius",Space,Str "Saturnia",Space,Str "iusto",LineBreak,Space,Str "Nec",Space,Str "pro",Space,Str "materia",Space,Str "fertur",Space,Str "doluisse",Space,Str "suique",LineBreak,Space,Str "Iudicis",Space,Str "aeterna",Space,Str "damnavit",Space,Str "lumina",Space,Str "nocte,",LineBreak,Space,Str "At",Space,Str "pater",Space,Str "omnipotens",Space,Str "(neque",Space,Str "enim",Space,Str "licet",Space,Str "inrita",Space,Str "cuiquam",LineBreak,Space,Str "Facta",Space,Str "dei",Space,Str "fecisse",Space,Str "deo)",Space,Str "pro",Space,Str "lumine",Space,Str "adempto",LineBreak,Space,Str "Scire",Space,Str "futura",Space,Str "dedit",Space,Str "poenamque",Space,Str "levavit",Space,Str "honore.",LineBreak]]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Old",Space,Str "man",Space,Str "with",Space,Str "wrinkled",Space,Str "female",Space,Str "breasts,",Space,Str "can",Space,Str "see"]] [Plain [Str "Old",Space,Str "man",Space,Str "with",Space,Str "wrinkled",Space,Str "female",Space,Str "breasts,",Space,Str "can",Space,Str "see"]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "At",Space,Str "the",Space,Str "violet",Space,Str "hour,",Space,Str "the",Space,Str "evening",Space,Str "hour",Space,Str "that",Space,Str "strives",Span ("",["lnum"],[]) [Str "220"]]] [Plain [Str "At",Space,Str "the",Space,Str "violet",Space,Str "hour,",Space,Str "the",Space,Str "evening",Space,Str "hour",Space,Str "that",Space,Str "strives",Span ("",["lnum"],[]) [Str "220"]]]
,Div ("wasteland-content.xhtml#ln221",[],[]) ,Div ("wasteland-content.xhtml#ln221",[],[])
[Plain [Str "Homeward,",Space,Str "and",Space,Str "brings",Space,Str "the",Space,Str "sailor",Space,Str "home",Space,Str "from",Space,Str "sea,",Note [Para [Link [Str "221."] ("#wasteland-content.xhtml#ln221",""),Space,Str "This",Space,Str "may",Space,Str "not",Space,Str "appear",Space,Str "as",Space,Str "exact",Space,Str "as",Space,Str "Sappho's",Space,Str "lines,",Space,Str "but",Space,Str "I",Space,Str "had",Space,Str "in",Space,Str "mind",Space,Str "the",Space,Str "\"longshore\"",Space,Str "or",Space,Str "\"dory\"",Space,Str "fisherman,",Space,Str "who",Space,Str "returns",Space,Str "at",Space,Str "nightfall."]]] [Plain [Str "Homeward,",Space,Str "and",Space,Str "brings",Space,Str "the",Space,Str "sailor",Space,Str "home",Space,Str "from",Space,Str "sea,",Note [Para [Link ("",[],[]) [Str "221."] ("#wasteland-content.xhtml#ln221",""),Space,Str "This",Space,Str "may",Space,Str "not",Space,Str "appear",Space,Str "as",Space,Str "exact",Space,Str "as",Space,Str "Sappho's",Space,Str "lines,",Space,Str "but",Space,Str "I",Space,Str "had",Space,Str "in",Space,Str "mind",Space,Str "the",Space,Str "\"longshore\"",Space,Str "or",Space,Str "\"dory\"",Space,Str "fisherman,",Space,Str "who",Space,Str "returns",Space,Str "at",Space,Str "nightfall."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "The",Space,Str "typist",Space,Str "home",Space,Str "at",Space,Str "teatime,",Space,Str "clears",Space,Str "her",Space,Str "breakfast,",Space,Str "lights"]] [Plain [Str "The",Space,Str "typist",Space,Str "home",Space,Str "at",Space,Str "teatime,",Space,Str "clears",Space,Str "her",Space,Str "breakfast,",Space,Str "lights"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -537,7 +537,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "\"Well",Space,Str "now",Space,Str "that's",Space,Str "done:",Space,Str "and",Space,Str "I'm",Space,Str "glad",Space,Str "it's",Space,Str "over.\""]] [Plain [Str "\"Well",Space,Str "now",Space,Str "that's",Space,Str "done:",Space,Str "and",Space,Str "I'm",Space,Str "glad",Space,Str "it's",Space,Str "over.\""]]
,Div ("wasteland-content.xhtml#ln253",[],[]) ,Div ("wasteland-content.xhtml#ln253",[],[])
[Plain [Str "When",Space,Str "lovely",Space,Str "woman",Space,Str "stoops",Space,Str "to",Space,Str "folly",Space,Str "and",Note [Para [Link [Str "253."] ("#wasteland-content.xhtml#ln253",""),Space,Str "V.",Space,Str "Goldsmith,",Space,Str "the",Space,Str "song",Space,Str "in",Space,Str "The",Space,Str "Vicar",Space,Str "of",Space,Str "Wakefield."]]] [Plain [Str "When",Space,Str "lovely",Space,Str "woman",Space,Str "stoops",Space,Str "to",Space,Str "folly",Space,Str "and",Note [Para [Link ("",[],[]) [Str "253."] ("#wasteland-content.xhtml#ln253",""),Space,Str "V.",Space,Str "Goldsmith,",Space,Str "the",Space,Str "song",Space,Str "in",Space,Str "The",Space,Str "Vicar",Space,Str "of",Space,Str "Wakefield."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Paces",Space,Str "about",Space,Str "her",Space,Str "room",Space,Str "again,",Space,Str "alone,"]] [Plain [Str "Paces",Space,Str "about",Space,Str "her",Space,Str "room",Space,Str "again,",Space,Str "alone,"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -546,7 +546,7 @@
[Plain [Str "And",Space,Str "puts",Space,Str "a",Space,Str "record",Space,Str "on",Space,Str "the",Space,Str "gramophone."]]] [Plain [Str "And",Space,Str "puts",Space,Str "a",Space,Str "record",Space,Str "on",Space,Str "the",Space,Str "gramophone."]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("wasteland-content.xhtml#ln257",[],[]) [Div ("wasteland-content.xhtml#ln257",[],[])
[Plain [Str "\"This",Space,Str "music",Space,Str "crept",Space,Str "by",Space,Str "me",Space,Str "upon",Space,Str "the",Space,Str "waters\"",Note [Para [Link [Str "257."] ("#wasteland-content.xhtml#ln257",""),Space,Str "V.",Space,Str "The",Space,Str "Tempest,",Space,Str "as",Space,Str "above."]]] [Plain [Str "\"This",Space,Str "music",Space,Str "crept",Space,Str "by",Space,Str "me",Space,Str "upon",Space,Str "the",Space,Str "waters\"",Note [Para [Link ("",[],[]) [Str "257."] ("#wasteland-content.xhtml#ln257",""),Space,Str "V.",Space,Str "The",Space,Str "Tempest,",Space,Str "as",Space,Str "above."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "And",Space,Str "along",Space,Str "the",Space,Str "Strand,",Space,Str "up",Space,Str "Queen",Space,Str "Victoria",Space,Str "Street."]] [Plain [Str "And",Space,Str "along",Space,Str "the",Space,Str "Strand,",Space,Str "up",Space,Str "Queen",Space,Str "Victoria",Space,Str "Street."]]
,Div ("",[],[]) ,Div ("",[],[])
@ -560,12 +560,12 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Where",Space,Str "fishmen",Space,Str "lounge",Space,Str "at",Space,Str "noon:",Space,Str "where",Space,Str "the",Space,Str "walls"]] [Plain [Str "Where",Space,Str "fishmen",Space,Str "lounge",Space,Str "at",Space,Str "noon:",Space,Str "where",Space,Str "the",Space,Str "walls"]]
,Div ("wasteland-content.xhtml#ln264",[],[]) ,Div ("wasteland-content.xhtml#ln264",[],[])
[Plain [Str "Of",Space,Str "Magnus",Space,Str "Martyr",Space,Str "hold",Note [Para [Link [Str "264."] ("#wasteland-content.xhtml#ln264",""),Space,Str "The",Space,Str "interior",Space,Str "of",Space,Str "St.",Space,Str "Magnus",Space,Str "Martyr",Space,Str "is",Space,Str "to",Space,Str "my",Space,Str "mind",Space,Str "one",Space,Str "of",Space,Str "the",Space,Str "finest",Space,Str "among",Space,Str "Wren's",Space,Str "interiors.",Space,Str "See",Space,Str "The",Space,Str "Proposed",Space,Str "Demolition",Space,Str "of",Space,Str "Nineteen",Space,Str "City",Space,Str "Churches",Space,Str "(P.",Space,Str "S.",Space,Str "King",Space,Str "&",Space,Str "Son,",Space,Str "Ltd.)."]]] [Plain [Str "Of",Space,Str "Magnus",Space,Str "Martyr",Space,Str "hold",Note [Para [Link ("",[],[]) [Str "264."] ("#wasteland-content.xhtml#ln264",""),Space,Str "The",Space,Str "interior",Space,Str "of",Space,Str "St.",Space,Str "Magnus",Space,Str "Martyr",Space,Str "is",Space,Str "to",Space,Str "my",Space,Str "mind",Space,Str "one",Space,Str "of",Space,Str "the",Space,Str "finest",Space,Str "among",Space,Str "Wren's",Space,Str "interiors.",Space,Str "See",Space,Str "The",Space,Str "Proposed",Space,Str "Demolition",Space,Str "of",Space,Str "Nineteen",Space,Str "City",Space,Str "Churches",Space,Str "(P.",Space,Str "S.",Space,Str "King",Space,Str "&",Space,Str "Son,",Space,Str "Ltd.)."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Inexplicable",Space,Str "splendour",Space,Str "of",Space,Str "Ionian",Space,Str "white",Space,Str "and",Space,Str "gold."]]] [Plain [Str "Inexplicable",Space,Str "splendour",Space,Str "of",Space,Str "Ionian",Space,Str "white",Space,Str "and",Space,Str "gold."]]]
,Div ("",["linegroup","indent"],[]) ,Div ("",["linegroup","indent"],[])
[Div ("wasteland-content.xhtml#ln266",[],[]) [Div ("wasteland-content.xhtml#ln266",[],[])
[Plain [Str "The",Space,Str "river",Space,Str "sweats",Note [Para [Link [Str "266."] ("#wasteland-content.xhtml#ln266",""),Space,Str "The",Space,Str "Song",Space,Str "of",Space,Str "the",Space,Str "(three)",Space,Str "Thames-daughters",Space,Str "begins",Space,Str "here.",Space,Str "From",Space,Str "line",Space,Str "292",Space,Str "to",Space,Str "306",Space,Str "inclusive",Space,Str "they",Space,Str "speak",Space,Str "in",Space,Str "turn.",Space,Str "V.",Space,Str "Gutterdsammerung,",Space,Str "III.",Space,Str "i:",Space,Str "the",Space,Str "Rhine-daughters."]]] [Plain [Str "The",Space,Str "river",Space,Str "sweats",Note [Para [Link ("",[],[]) [Str "266."] ("#wasteland-content.xhtml#ln266",""),Space,Str "The",Space,Str "Song",Space,Str "of",Space,Str "the",Space,Str "(three)",Space,Str "Thames-daughters",Space,Str "begins",Space,Str "here.",Space,Str "From",Space,Str "line",Space,Str "292",Space,Str "to",Space,Str "306",Space,Str "inclusive",Space,Str "they",Space,Str "speak",Space,Str "in",Space,Str "turn.",Space,Str "V.",Space,Str "Gutterdsammerung,",Space,Str "III.",Space,Str "i:",Space,Str "the",Space,Str "Rhine-daughters."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Oil",Space,Str "and",Space,Str "tar"]] [Plain [Str "Oil",Space,Str "and",Space,Str "tar"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -592,7 +592,7 @@
[Plain [Str "Wallala",Space,Str "leialala"]]] [Plain [Str "Wallala",Space,Str "leialala"]]]
,Div ("",["linegroup","indent"],[]) ,Div ("",["linegroup","indent"],[])
[Div ("wasteland-content.xhtml#ln279",[],[]) [Div ("wasteland-content.xhtml#ln279",[],[])
[Plain [Str "Elizabeth",Space,Str "and",Space,Str "Leicester",Note [Para [Link [Str "279."] ("#wasteland-content.xhtml#ln279",""),Space,Str "V.",Space,Str "Froude,",Space,Str "Elizabeth,",Space,Str "Vol.",Space,Str "I,",Space,Str "ch.",Space,Str "iv,",Space,Str "letter",Space,Str "of",Space,Str "De",Space,Str "Quadra",Space,Str "to",Space,Str "Philip",Space,Str "of",Space,Str "Spain:"],BlockQuote [Div ("",[],[]) [Div ("",[],[]) [Plain [Str "\"In",Space,Str "the",Space,Str "afternoon",Space,Str "we",Space,Str "were",Space,Str "in",Space,Str "a",Space,Str "barge,",Space,Str "watching",Space,Str "the",Space,Str "games",Space,Str "on",Space,Str "the",Space,Str "river."]],Div ("",[],[]) [Plain [Str "(The",Space,Str "queen)",Space,Str "was",Space,Str "alone",Space,Str "with",Space,Str "Lord",Space,Str "Robert",Space,Str "and",Space,Str "myself",Space,Str "on",Space,Str "the",Space,Str "poop,"]],Div ("",[],[]) [Plain [Str "when",Space,Str "they",Space,Str "began",Space,Str "to",Space,Str "talk",Space,Str "nonsense,",Space,Str "and",Space,Str "went",Space,Str "so",Space,Str "far",Space,Str "that",Space,Str "Lord",Space,Str "Robert"]],Div ("",[],[]) [Plain [Str "at",Space,Str "last",Space,Str "said,",Space,Str "as",Space,Str "I",Space,Str "was",Space,Str "on",Space,Str "the",Space,Str "spot",Space,Str "there",Space,Str "was",Space,Str "no",Space,Str "reason",Space,Str "why",Space,Str "they"]],Div ("",[],[]) [Plain [Str "should",Space,Str "not",Space,Str "be",Space,Str "married",Space,Str "if",Space,Str "the",Space,Str "queen",Space,Str "pleased.\""]]]]]] [Plain [Str "Elizabeth",Space,Str "and",Space,Str "Leicester",Note [Para [Link ("",[],[]) [Str "279."] ("#wasteland-content.xhtml#ln279",""),Space,Str "V.",Space,Str "Froude,",Space,Str "Elizabeth,",Space,Str "Vol.",Space,Str "I,",Space,Str "ch.",Space,Str "iv,",Space,Str "letter",Space,Str "of",Space,Str "De",Space,Str "Quadra",Space,Str "to",Space,Str "Philip",Space,Str "of",Space,Str "Spain:"],BlockQuote [Div ("",[],[]) [Div ("",[],[]) [Plain [Str "\"In",Space,Str "the",Space,Str "afternoon",Space,Str "we",Space,Str "were",Space,Str "in",Space,Str "a",Space,Str "barge,",Space,Str "watching",Space,Str "the",Space,Str "games",Space,Str "on",Space,Str "the",Space,Str "river."]],Div ("",[],[]) [Plain [Str "(The",Space,Str "queen)",Space,Str "was",Space,Str "alone",Space,Str "with",Space,Str "Lord",Space,Str "Robert",Space,Str "and",Space,Str "myself",Space,Str "on",Space,Str "the",Space,Str "poop,"]],Div ("",[],[]) [Plain [Str "when",Space,Str "they",Space,Str "began",Space,Str "to",Space,Str "talk",Space,Str "nonsense,",Space,Str "and",Space,Str "went",Space,Str "so",Space,Str "far",Space,Str "that",Space,Str "Lord",Space,Str "Robert"]],Div ("",[],[]) [Plain [Str "at",Space,Str "last",Space,Str "said,",Space,Str "as",Space,Str "I",Space,Str "was",Space,Str "on",Space,Str "the",Space,Str "spot",Space,Str "there",Space,Str "was",Space,Str "no",Space,Str "reason",Space,Str "why",Space,Str "they"]],Div ("",[],[]) [Plain [Str "should",Space,Str "not",Space,Str "be",Space,Str "married",Space,Str "if",Space,Str "the",Space,Str "queen",Space,Str "pleased.\""]]]]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Beating",Space,Str "oars",Span ("",["lnum"],[]) [Str "280"]]] [Plain [Str "Beating",Space,Str "oars",Span ("",["lnum"],[]) [Str "280"]]]
,Div ("",[],[]) ,Div ("",[],[])
@ -621,7 +621,7 @@
[Div ("",[],[]) [Div ("",[],[])
[Plain [Str "\"Trams",Space,Str "and",Space,Str "dusty",Space,Str "trees."]] [Plain [Str "\"Trams",Space,Str "and",Space,Str "dusty",Space,Str "trees."]]
,Div ("wasteland-content.xhtml#ln293",[],[]) ,Div ("wasteland-content.xhtml#ln293",[],[])
[Plain [Str "Highbury",Space,Str "bore",Space,Str "me.",Space,Str "Richmond",Space,Str "and",Space,Str "Kew",Note [Para [Link [Str "293."] ("#wasteland-content.xhtml#ln293",""),Space,Str "Cf.",Space,Str "Purgatorio,",Space,Str "v.",Space,Str "133:"],BlockQuote [Para [Str "\"Ricorditi",Space,Str "di",Space,Str "me,",Space,Str "che",Space,Str "son",Space,Str "la",Space,Str "Pia;",LineBreak,Str "Siena",Space,Str "mi",Space,Str "fe',",Space,Str "disfecemi",Space,Str "Maremma.\""]]]] [Plain [Str "Highbury",Space,Str "bore",Space,Str "me.",Space,Str "Richmond",Space,Str "and",Space,Str "Kew",Note [Para [Link ("",[],[]) [Str "293."] ("#wasteland-content.xhtml#ln293",""),Space,Str "Cf.",Space,Str "Purgatorio,",Space,Str "v.",Space,Str "133:"],BlockQuote [Para [Str "\"Ricorditi",Space,Str "di",Space,Str "me,",Space,Str "che",Space,Str "son",Space,Str "la",Space,Str "Pia;",LineBreak,Str "Siena",Space,Str "mi",Space,Str "fe',",Space,Str "disfecemi",Space,Str "Maremma.\""]]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Undid",Space,Str "me.",Space,Str "By",Space,Str "Richmond",Space,Str "I",Space,Str "raised",Space,Str "my",Space,Str "knees"]] [Plain [Str "Undid",Space,Str "me.",Space,Str "By",Space,Str "Richmond",Space,Str "I",Space,Str "raised",Space,Str "my",Space,Str "knees"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -651,12 +651,12 @@
[Plain [Str "la",Space,Str "la"]]] [Plain [Str "la",Space,Str "la"]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("wasteland-content.xhtml#ln307",[],[]) [Div ("wasteland-content.xhtml#ln307",[],[])
[Plain [Str "To",Space,Str "Carthage",Space,Str "then",Space,Str "I",Space,Str "came",Note [Para [Link [Str "307."] ("#wasteland-content.xhtml#ln307",""),Space,Str "V.",Space,Str "St.",Space,Str "Augustine's",Space,Str "Confessions:",Space,Str "\"to",Space,Str "Carthage",Space,Str "then",Space,Str "I",Space,Str "came,",Space,Str "where",Space,Str "a",Space,Str "cauldron",Space,Str "of",Space,Str "unholy",Space,Str "loves",Space,Str "sang",Space,Str "all",Space,Str "about",Space,Str "mine",Space,Str "ears.\""]]] [Plain [Str "To",Space,Str "Carthage",Space,Str "then",Space,Str "I",Space,Str "came",Note [Para [Link ("",[],[]) [Str "307."] ("#wasteland-content.xhtml#ln307",""),Space,Str "V.",Space,Str "St.",Space,Str "Augustine's",Space,Str "Confessions:",Space,Str "\"to",Space,Str "Carthage",Space,Str "then",Space,Str "I",Space,Str "came,",Space,Str "where",Space,Str "a",Space,Str "cauldron",Space,Str "of",Space,Str "unholy",Space,Str "loves",Space,Str "sang",Space,Str "all",Space,Str "about",Space,Str "mine",Space,Str "ears.\""]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("wasteland-content.xhtml#ln308",[],[]) [Div ("wasteland-content.xhtml#ln308",[],[])
[Plain [Str "Burning",Space,Str "burning",Space,Str "burning",Space,Str "burning",Note [Para [Link [Str "308."] ("#wasteland-content.xhtml#ln308",""),Space,Str "The",Space,Str "complete",Space,Str "text",Space,Str "of",Space,Str "the",Space,Str "Buddha's",Space,Str "Fire",Space,Str "Sermon",Space,Str "(which",Space,Str "corresponds",Space,Str "in",Space,Str "importance",Space,Str "to",Space,Str "the",Space,Str "Sermon",Space,Str "on",Space,Str "the",Space,Str "Mount)",Space,Str "from",Space,Str "which",Space,Str "these",Space,Str "words",Space,Str "are",Space,Str "taken,",Space,Str "will",Space,Str "be",Space,Str "found",Space,Str "translated",Space,Str "in",Space,Str "the",Space,Str "late",Space,Str "Henry",Space,Str "Clarke",Space,Str "Warren's",Space,Str "Buddhism",Space,Str "in",Space,Str "Translation",Space,Str "(Harvard",Space,Str "Oriental",Space,Str "Series).",Space,Str "Mr.",Space,Str "Warren",Space,Str "was",Space,Str "one",Space,Str "of",Space,Str "the",Space,Str "great",Space,Str "pioneers",Space,Str "of",Space,Str "Buddhist",Space,Str "studies",Space,Str "in",Space,Str "the",Space,Str "Occident."]]] [Plain [Str "Burning",Space,Str "burning",Space,Str "burning",Space,Str "burning",Note [Para [Link ("",[],[]) [Str "308."] ("#wasteland-content.xhtml#ln308",""),Space,Str "The",Space,Str "complete",Space,Str "text",Space,Str "of",Space,Str "the",Space,Str "Buddha's",Space,Str "Fire",Space,Str "Sermon",Space,Str "(which",Space,Str "corresponds",Space,Str "in",Space,Str "importance",Space,Str "to",Space,Str "the",Space,Str "Sermon",Space,Str "on",Space,Str "the",Space,Str "Mount)",Space,Str "from",Space,Str "which",Space,Str "these",Space,Str "words",Space,Str "are",Space,Str "taken,",Space,Str "will",Space,Str "be",Space,Str "found",Space,Str "translated",Space,Str "in",Space,Str "the",Space,Str "late",Space,Str "Henry",Space,Str "Clarke",Space,Str "Warren's",Space,Str "Buddhism",Space,Str "in",Space,Str "Translation",Space,Str "(Harvard",Space,Str "Oriental",Space,Str "Series).",Space,Str "Mr.",Space,Str "Warren",Space,Str "was",Space,Str "one",Space,Str "of",Space,Str "the",Space,Str "great",Space,Str "pioneers",Space,Str "of",Space,Str "Buddhist",Space,Str "studies",Space,Str "in",Space,Str "the",Space,Str "Occident."]]]
,Div ("wasteland-content.xhtml#ln309",[],[]) ,Div ("wasteland-content.xhtml#ln309",[],[])
[Plain [Str "O",Space,Str "Lord",Space,Str "Thou",Space,Str "pluckest",Space,Str "me",Space,Str "out",Note [Para [Link [Str "309."] ("#wasteland-content.xhtml#ln309",""),Space,Str "From",Space,Str "St.",Space,Str "Augustine's",Space,Str "Confessions",Space,Str "again.",Space,Str "The",Space,Str "collocation",Space,Str "of",Space,Str "these",Space,Str "two",Space,Str "representatives",Space,Str "of",Space,Str "eastern",Space,Str "and",Space,Str "western",Space,Str "asceticism,",Space,Str "as",Space,Str "the",Space,Str "culmination",Space,Str "of",Space,Str "this",Space,Str "part",Space,Str "of",Space,Str "the",Space,Str "poem,",Space,Str "is",Space,Str "not",Space,Str "an",Space,Str "accident."]]] [Plain [Str "O",Space,Str "Lord",Space,Str "Thou",Space,Str "pluckest",Space,Str "me",Space,Str "out",Note [Para [Link ("",[],[]) [Str "309."] ("#wasteland-content.xhtml#ln309",""),Space,Str "From",Space,Str "St.",Space,Str "Augustine's",Space,Str "Confessions",Space,Str "again.",Space,Str "The",Space,Str "collocation",Space,Str "of",Space,Str "these",Space,Str "two",Space,Str "representatives",Space,Str "of",Space,Str "eastern",Space,Str "and",Space,Str "western",Space,Str "asceticism,",Space,Str "as",Space,Str "the",Space,Str "culmination",Space,Str "of",Space,Str "this",Space,Str "part",Space,Str "of",Space,Str "the",Space,Str "poem,",Space,Str "is",Space,Str "not",Space,Str "an",Space,Str "accident."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "O",Space,Str "Lord",Space,Str "Thou",Space,Str "pluckest",Span ("",["lnum"],[]) [Str "310"]]]] [Plain [Str "O",Space,Str "Lord",Space,Str "Thou",Space,Str "pluckest",Span ("",["lnum"],[]) [Str "310"]]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
@ -764,14 +764,14 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "But",Space,Str "sound",Space,Str "of",Space,Str "water",Space,Str "over",Space,Str "a",Space,Str "rock"]] [Plain [Str "But",Space,Str "sound",Space,Str "of",Space,Str "water",Space,Str "over",Space,Str "a",Space,Str "rock"]]
,Div ("wasteland-content.xhtml#ln357",[],[]) ,Div ("wasteland-content.xhtml#ln357",[],[])
[Plain [Str "Where",Space,Str "the",Space,Str "hermit-thrush",Space,Str "sings",Space,Str "in",Space,Str "the",Space,Str "pine",Space,Str "trees",Note [Para [Link [Str "357."] ("#wasteland-content.xhtml#ln357",""),Space,Str "This",Space,Str "is",Space,Str "Turdus",Space,Str "aonalaschkae",Space,Str "pallasii,",Space,Str "the",Space,Str "hermit-thrush",Space,Str "which",Space,Str "I",Space,Str "have",Space,Str "heard",Space,Str "in",Space,Str "Quebec",Space,Str "County.",Space,Str "Chapman",Space,Str "says",Space,Str "(Handbook",Space,Str "of",Space,Str "Birds",Space,Str "of",Space,Str "Eastern",Space,Str "North",Space,Str "America)",Space,Str "\"it",Space,Str "is",Space,Str "most",Space,Str "at",Space,Str "home",Space,Str "in",Space,Str "secluded",Space,Str "woodland",Space,Str "and",Space,Str "thickety",Space,Str "retreats.",Space,Str ".",Space,Str ".",Space,Str ".",Space,Str "Its",Space,Str "notes",Space,Str "are",Space,Str "not",Space,Str "remarkable",Space,Str "for",Space,Str "variety",Space,Str "or",Space,Str "volume,",Space,Str "but",Space,Str "in",Space,Str "purity",Space,Str "and",Space,Str "sweetness",Space,Str "of",Space,Str "tone",Space,Str "and",Space,Str "exquisite",Space,Str "modulation",Space,Str "they",Space,Str "are",Space,Str "unequalled.\"",Space,Str "Its",Space,Str "\"water-dripping",Space,Str "song\"",Space,Str "is",Space,Str "justly",Space,Str "celebrated."]]] [Plain [Str "Where",Space,Str "the",Space,Str "hermit-thrush",Space,Str "sings",Space,Str "in",Space,Str "the",Space,Str "pine",Space,Str "trees",Note [Para [Link ("",[],[]) [Str "357."] ("#wasteland-content.xhtml#ln357",""),Space,Str "This",Space,Str "is",Space,Str "Turdus",Space,Str "aonalaschkae",Space,Str "pallasii,",Space,Str "the",Space,Str "hermit-thrush",Space,Str "which",Space,Str "I",Space,Str "have",Space,Str "heard",Space,Str "in",Space,Str "Quebec",Space,Str "County.",Space,Str "Chapman",Space,Str "says",Space,Str "(Handbook",Space,Str "of",Space,Str "Birds",Space,Str "of",Space,Str "Eastern",Space,Str "North",Space,Str "America)",Space,Str "\"it",Space,Str "is",Space,Str "most",Space,Str "at",Space,Str "home",Space,Str "in",Space,Str "secluded",Space,Str "woodland",Space,Str "and",Space,Str "thickety",Space,Str "retreats.",Space,Str ".",Space,Str ".",Space,Str ".",Space,Str "Its",Space,Str "notes",Space,Str "are",Space,Str "not",Space,Str "remarkable",Space,Str "for",Space,Str "variety",Space,Str "or",Space,Str "volume,",Space,Str "but",Space,Str "in",Space,Str "purity",Space,Str "and",Space,Str "sweetness",Space,Str "of",Space,Str "tone",Space,Str "and",Space,Str "exquisite",Space,Str "modulation",Space,Str "they",Space,Str "are",Space,Str "unequalled.\"",Space,Str "Its",Space,Str "\"water-dripping",Space,Str "song\"",Space,Str "is",Space,Str "justly",Space,Str "celebrated."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Drip",Space,Str "drop",Space,Str "drip",Space,Str "drop",Space,Str "drop",Space,Str "drop",Space,Str "drop"]] [Plain [Str "Drip",Space,Str "drop",Space,Str "drip",Space,Str "drop",Space,Str "drop",Space,Str "drop",Space,Str "drop"]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "But",Space,Str "there",Space,Str "is",Space,Str "no",Space,Str "water"]]]] [Plain [Str "But",Space,Str "there",Space,Str "is",Space,Str "no",Space,Str "water"]]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("wasteland-content.xhtml#ln360",[],[]) [Div ("wasteland-content.xhtml#ln360",[],[])
[Plain [Str "Who",Space,Str "is",Space,Str "the",Space,Str "third",Space,Str "who",Space,Str "walks",Space,Str "always",Space,Str "beside",Space,Str "you?",Note [Para [Link [Str "360."] ("#wasteland-content.xhtml#ln360",""),Space,Str "The",Space,Str "following",Space,Str "lines",Space,Str "were",Space,Str "stimulated",Space,Str "by",Space,Str "the",Space,Str "account",Space,Str "of",Space,Str "one",Space,Str "of",Space,Str "the",Space,Str "Antarctic",Space,Str "expeditions",Space,Str "(I",Space,Str "forget",Space,Str "which,",Space,Str "but",Space,Str "I",Space,Str "think",Space,Str "one",Space,Str "of",Space,Str "Shackleton's):",Space,Str "it",Space,Str "was",Space,Str "related",Space,Str "that",Space,Str "the",Space,Str "party",Space,Str "of",Space,Str "explorers,",Space,Str "at",Space,Str "the",Space,Str "extremity",Space,Str "of",Space,Str "their",Space,Str "strength,",Space,Str "had",Space,Str "the",Space,Str "constant",Space,Str "delusion",Space,Str "that",Space,Str "there",Space,Str "was",Space,Str "one",Space,Str "more",Space,Str "member",Space,Str "than",Space,Str "could",Space,Str "actually",Space,Str "be",Space,Str "counted."]]] [Plain [Str "Who",Space,Str "is",Space,Str "the",Space,Str "third",Space,Str "who",Space,Str "walks",Space,Str "always",Space,Str "beside",Space,Str "you?",Note [Para [Link ("",[],[]) [Str "360."] ("#wasteland-content.xhtml#ln360",""),Space,Str "The",Space,Str "following",Space,Str "lines",Space,Str "were",Space,Str "stimulated",Space,Str "by",Space,Str "the",Space,Str "account",Space,Str "of",Space,Str "one",Space,Str "of",Space,Str "the",Space,Str "Antarctic",Space,Str "expeditions",Space,Str "(I",Space,Str "forget",Space,Str "which,",Space,Str "but",Space,Str "I",Space,Str "think",Space,Str "one",Space,Str "of",Space,Str "Shackleton's):",Space,Str "it",Space,Str "was",Space,Str "related",Space,Str "that",Space,Str "the",Space,Str "party",Space,Str "of",Space,Str "explorers,",Space,Str "at",Space,Str "the",Space,Str "extremity",Space,Str "of",Space,Str "their",Space,Str "strength,",Space,Str "had",Space,Str "the",Space,Str "constant",Space,Str "delusion",Space,Str "that",Space,Str "there",Space,Str "was",Space,Str "one",Space,Str "more",Space,Str "member",Space,Str "than",Space,Str "could",Space,Str "actually",Space,Str "be",Space,Str "counted."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "When",Space,Str "I",Space,Str "count,",Space,Str "there",Space,Str "are",Space,Str "only",Space,Str "you",Space,Str "and",Space,Str "I",Space,Str "together"]] [Plain [Str "When",Space,Str "I",Space,Str "count,",Space,Str "there",Space,Str "are",Space,Str "only",Space,Str "you",Space,Str "and",Space,Str "I",Space,Str "together"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -783,7 +783,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "I",Space,Str "do",Space,Str "not",Space,Str "know",Space,Str "whether",Space,Str "a",Space,Str "man",Space,Str "or",Space,Str "a",Space,Str "woman"]] [Plain [Str "I",Space,Str "do",Space,Str "not",Space,Str "know",Space,Str "whether",Space,Str "a",Space,Str "man",Space,Str "or",Space,Str "a",Space,Str "woman"]]
,Div ("wasteland-content.xhtml#ln367",[],[]) ,Div ("wasteland-content.xhtml#ln367",[],[])
[Plain [Str "\8213But",Space,Str "who",Space,Str "is",Space,Str "that",Space,Str "on",Space,Str "the",Space,Str "other",Space,Str "side",Space,Str "of",Space,Str "you?",Note [Para [Link [Str "367-77."] ("#wasteland-content.xhtml#ln367",""),Space,Str "Cf.",Space,Str "Hermann",Space,Str "Hesse,",Space,Str "Blick",Space,Str "ins",Space,Str "Chaos:"],BlockQuote [Para [Str "\"Schon",Space,Str "ist",Space,Str "halb",Space,Str "Europa,",Space,Str "schon",Space,Str "ist",Space,Str "zumindest",Space,Str "der",Space,Str "halbe",Space,Str "Osten",Space,Str "Europas",Space,Str "auf",Space,Str "dem",LineBreak,Space,Str "Wege",Space,Str "zum",Space,Str "Chaos,",Space,Str "fhrt",Space,Str "betrunken",Space,Str "im",Space,Str "heiligem",Space,Str "Wahn",Space,Str "am",Space,Str "Abgrund",Space,Str "entlang",LineBreak,Space,Str "und",Space,Str "singt",Space,Str "dazu,",Space,Str "singt",Space,Str "betrunken",Space,Str "und",Space,Str "hymnisch",Space,Str "wie",Space,Str "Dmitri",Space,Str "Karamasoff",Space,Str "sang.",LineBreak,Space,Str "Ueber",Space,Str "diese",Space,Str "Lieder",Space,Str "lacht",Space,Str "der",Space,Str "Bsrger",Space,Str "beleidigt,",Space,Str "der",Space,Str "Heilige",LineBreak,Space,Str "und",Space,Str "Seher",Space,Str "hrt",Space,Str "sie",Space,Str "mit",Space,Str "Trvnen.\""]]]] [Plain [Str "\8213But",Space,Str "who",Space,Str "is",Space,Str "that",Space,Str "on",Space,Str "the",Space,Str "other",Space,Str "side",Space,Str "of",Space,Str "you?",Note [Para [Link ("",[],[]) [Str "367-77."] ("#wasteland-content.xhtml#ln367",""),Space,Str "Cf.",Space,Str "Hermann",Space,Str "Hesse,",Space,Str "Blick",Space,Str "ins",Space,Str "Chaos:"],BlockQuote [Para [Str "\"Schon",Space,Str "ist",Space,Str "halb",Space,Str "Europa,",Space,Str "schon",Space,Str "ist",Space,Str "zumindest",Space,Str "der",Space,Str "halbe",Space,Str "Osten",Space,Str "Europas",Space,Str "auf",Space,Str "dem",LineBreak,Space,Str "Wege",Space,Str "zum",Space,Str "Chaos,",Space,Str "fhrt",Space,Str "betrunken",Space,Str "im",Space,Str "heiligem",Space,Str "Wahn",Space,Str "am",Space,Str "Abgrund",Space,Str "entlang",LineBreak,Space,Str "und",Space,Str "singt",Space,Str "dazu,",Space,Str "singt",Space,Str "betrunken",Space,Str "und",Space,Str "hymnisch",Space,Str "wie",Space,Str "Dmitri",Space,Str "Karamasoff",Space,Str "sang.",LineBreak,Space,Str "Ueber",Space,Str "diese",Space,Str "Lieder",Space,Str "lacht",Space,Str "der",Space,Str "Bsrger",Space,Str "beleidigt,",Space,Str "der",Space,Str "Heilige",LineBreak,Space,Str "und",Space,Str "Seher",Space,Str "hrt",Space,Str "sie",Space,Str "mit",Space,Str "Trvnen.\""]]]]
,Div ("",["linegroup"],[]) ,Div ("",["linegroup"],[])
[Div ("",[],[]) [Div ("",[],[])
[Plain [Str "What",Space,Str "is",Space,Str "that",Space,Str "sound",Space,Str "high",Space,Str "in",Space,Str "the",Space,Str "air"]] [Plain [Str "What",Space,Str "is",Space,Str "that",Space,Str "sound",Space,Str "high",Space,Str "in",Space,Str "the",Space,Str "air"]]
@ -859,7 +859,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "DA"]] [Plain [Str "DA"]]
,Div ("wasteland-content.xhtml#ln402",[],[]) ,Div ("wasteland-content.xhtml#ln402",[],[])
[Plain [Span ("",[],[("lang","sa")]) [Str "Datta"],Str ":",Space,Str "what",Space,Str "have",Space,Str "we",Space,Str "given?",Note [Para [Link [Str "402."] ("#wasteland-content.xhtml#ln402",""),Space,Quoted DoubleQuote [Str "\"Datta,",Space,Str "dayadhvam,",Space,Str "damyata\""],Space,Str "(Give,",Space,Str "sympathize,",Space,Str "control).",Space,Str "The",Space,Str "fable",Space,Str "of",Space,Str "the",Space,Str "meaning",Space,Str "of",Space,Str "the",Space,Str "Thunder",Space,Str "is",Space,Str "found",Space,Str "in",Space,Str "the",Space,Str "Brihadaranyaka-Upanishad,",Space,Str "5,",Space,Str "1.",Space,Str "A",Space,Str "translation",Space,Str "is",Space,Str "found",Space,Str "in",Space,Str "Deussen's",Space,Str "Sechzig",Space,Str "Upanishads",Space,Str "des",Space,Str "Veda,",Space,Str "p.",Space,Str "489."]]] [Plain [Span ("",[],[("lang","sa")]) [Str "Datta"],Str ":",Space,Str "what",Space,Str "have",Space,Str "we",Space,Str "given?",Note [Para [Link ("",[],[]) [Str "402."] ("#wasteland-content.xhtml#ln402",""),Space,Quoted DoubleQuote [Str "\"Datta,",Space,Str "dayadhvam,",Space,Str "damyata\""],Space,Str "(Give,",Space,Str "sympathize,",Space,Str "control).",Space,Str "The",Space,Str "fable",Space,Str "of",Space,Str "the",Space,Str "meaning",Space,Str "of",Space,Str "the",Space,Str "Thunder",Space,Str "is",Space,Str "found",Space,Str "in",Space,Str "the",Space,Str "Brihadaranyaka-Upanishad,",Space,Str "5,",Space,Str "1.",Space,Str "A",Space,Str "translation",Space,Str "is",Space,Str "found",Space,Str "in",Space,Str "Deussen's",Space,Str "Sechzig",Space,Str "Upanishads",Space,Str "des",Space,Str "Veda,",Space,Str "p.",Space,Str "489."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "My",Space,Str "friend,",Space,Str "blood",Space,Str "shaking",Space,Str "my",Space,Str "heart"]] [Plain [Str "My",Space,Str "friend,",Space,Str "blood",Space,Str "shaking",Space,Str "my",Space,Str "heart"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -871,7 +871,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Which",Space,Str "is",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "found",Space,Str "in",Space,Str "our",Space,Str "obituaries"]] [Plain [Str "Which",Space,Str "is",Space,Str "not",Space,Str "to",Space,Str "be",Space,Str "found",Space,Str "in",Space,Str "our",Space,Str "obituaries"]]
,Div ("wasteland-content.xhtml#ln408",[],[]) ,Div ("wasteland-content.xhtml#ln408",[],[])
[Plain [Str "Or",Space,Str "in",Space,Str "memories",Space,Str "draped",Space,Str "by",Space,Str "the",Space,Str "beneficent",Space,Str "spider",Note [Para [Link [Str "408."] ("#wasteland-content.xhtml#ln408",""),Space,Str "Cf.",Space,Str "Webster,",Space,Str "The",Space,Str "White",Space,Str "Devil,",Space,Str "v.",Space,Str "vi:"],BlockQuote [Para [Str "\".",Space,Str ".",Space,Str ".",Space,Str "they'll",Space,Str "remarry",LineBreak,Space,Str "Ere",Space,Str "the",Space,Str "worm",Space,Str "pierce",Space,Str "your",Space,Str "winding-sheet,",Space,Str "ere",Space,Str "the",Space,Str "spider",LineBreak,Space,Str "Make",Space,Str "a",Space,Str "thin",Space,Str "curtain",Space,Str "for",Space,Str "your",Space,Str "epitaphs.\""]]]] [Plain [Str "Or",Space,Str "in",Space,Str "memories",Space,Str "draped",Space,Str "by",Space,Str "the",Space,Str "beneficent",Space,Str "spider",Note [Para [Link ("",[],[]) [Str "408."] ("#wasteland-content.xhtml#ln408",""),Space,Str "Cf.",Space,Str "Webster,",Space,Str "The",Space,Str "White",Space,Str "Devil,",Space,Str "v.",Space,Str "vi:"],BlockQuote [Para [Str "\".",Space,Str ".",Space,Str ".",Space,Str "they'll",Space,Str "remarry",LineBreak,Space,Str "Ere",Space,Str "the",Space,Str "worm",Space,Str "pierce",Space,Str "your",Space,Str "winding-sheet,",Space,Str "ere",Space,Str "the",Space,Str "spider",LineBreak,Space,Str "Make",Space,Str "a",Space,Str "thin",Space,Str "curtain",Space,Str "for",Space,Str "your",Space,Str "epitaphs.\""]]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Or",Space,Str "under",Space,Str "seals",Space,Str "broken",Space,Str "by",Space,Str "the",Space,Str "lean",Space,Str "solicitor"]] [Plain [Str "Or",Space,Str "under",Space,Str "seals",Space,Str "broken",Space,Str "by",Space,Str "the",Space,Str "lean",Space,Str "solicitor"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -879,7 +879,7 @@
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "DA"]] [Plain [Str "DA"]]
,Div ("wasteland-content.xhtml#ln412",[],[]) ,Div ("wasteland-content.xhtml#ln412",[],[])
[Plain [Span ("",[],[("lang","sa")]) [Str "Dayadhvam"],Str ":",Space,Str "I",Space,Str "have",Space,Str "heard",Space,Str "the",Space,Str "key",Note [Para [Link [Str "412."] ("#wasteland-content.xhtml#ln412",""),Space,Str "Cf.",Space,Str "Inferno,",Space,Str "xxxiii.",Space,Str "46:"],BlockQuote [Para [Str "\"ed",Space,Str "io",Space,Str "sentii",Space,Str "chiavar",Space,Str "l'uscio",Space,Str "di",Space,Str "sotto",LineBreak,Space,Str "all'orribile",Space,Str "torre.\""]],Para [Str "Also",Space,Str "F.",Space,Str "H.",Space,Str "Bradley,",Space,Str "Appearance",Space,Str "and",Space,Str "Reality,",Space,Str "p.",Space,Str "346:"],BlockQuote [Para [Str "\"My",Space,Str "external",Space,Str "sensations",Space,Str "are",Space,Str "no",Space,Str "less",Space,Str "private",Space,Str "to",Space,Str "myself",Space,Str "than",Space,Str "are",Space,Str "my",Space,Str "thoughts",Space,Str "or",Space,Str "my",Space,Str "feelings.",Space,Str "In",Space,Str "either",Space,Str "case",Space,Str "my",Space,Str "experience",Space,Str "falls",Space,Str "within",Space,Str "my",Space,Str "own",Space,Str "circle,",Space,Str "a",Space,Str "circle",Space,Str "closed",Space,Str "on",Space,Str "the",Space,Str "outside;",Space,Str "and,",Space,Str "with",Space,Str "all",Space,Str "its",Space,Str "elements",Space,Str "alike,",Space,Str "every",Space,Str "sphere",Space,Str "is",Space,Str "opaque",Space,Str "to",Space,Str "the",Space,Str "others",Space,Str "which",Space,Str "surround",Space,Str "it.",Space,Str ".",Space,Str ".",Space,Str ".",Space,Str "In",Space,Str "brief,",Space,Str "regarded",Space,Str "as",Space,Str "an",Space,Str "existence",Space,Str "which",Space,Str "appears",Space,Str "in",Space,Str "a",Space,Str "soul,",Space,Str "the",Space,Str "whole",Space,Str "world",Space,Str "for",Space,Str "each",Space,Str "is",Space,Str "peculiar",Space,Str "and",Space,Str "private",Space,Str "to",Space,Str "that",Space,Str "soul.\""]]]] [Plain [Span ("",[],[("lang","sa")]) [Str "Dayadhvam"],Str ":",Space,Str "I",Space,Str "have",Space,Str "heard",Space,Str "the",Space,Str "key",Note [Para [Link ("",[],[]) [Str "412."] ("#wasteland-content.xhtml#ln412",""),Space,Str "Cf.",Space,Str "Inferno,",Space,Str "xxxiii.",Space,Str "46:"],BlockQuote [Para [Str "\"ed",Space,Str "io",Space,Str "sentii",Space,Str "chiavar",Space,Str "l'uscio",Space,Str "di",Space,Str "sotto",LineBreak,Space,Str "all'orribile",Space,Str "torre.\""]],Para [Str "Also",Space,Str "F.",Space,Str "H.",Space,Str "Bradley,",Space,Str "Appearance",Space,Str "and",Space,Str "Reality,",Space,Str "p.",Space,Str "346:"],BlockQuote [Para [Str "\"My",Space,Str "external",Space,Str "sensations",Space,Str "are",Space,Str "no",Space,Str "less",Space,Str "private",Space,Str "to",Space,Str "myself",Space,Str "than",Space,Str "are",Space,Str "my",Space,Str "thoughts",Space,Str "or",Space,Str "my",Space,Str "feelings.",Space,Str "In",Space,Str "either",Space,Str "case",Space,Str "my",Space,Str "experience",Space,Str "falls",Space,Str "within",Space,Str "my",Space,Str "own",Space,Str "circle,",Space,Str "a",Space,Str "circle",Space,Str "closed",Space,Str "on",Space,Str "the",Space,Str "outside;",Space,Str "and,",Space,Str "with",Space,Str "all",Space,Str "its",Space,Str "elements",Space,Str "alike,",Space,Str "every",Space,Str "sphere",Space,Str "is",Space,Str "opaque",Space,Str "to",Space,Str "the",Space,Str "others",Space,Str "which",Space,Str "surround",Space,Str "it.",Space,Str ".",Space,Str ".",Space,Str ".",Space,Str "In",Space,Str "brief,",Space,Str "regarded",Space,Str "as",Space,Str "an",Space,Str "existence",Space,Str "which",Space,Str "appears",Space,Str "in",Space,Str "a",Space,Str "soul,",Space,Str "the",Space,Str "whole",Space,Str "world",Space,Str "for",Space,Str "each",Space,Str "is",Space,Str "peculiar",Space,Str "and",Space,Str "private",Space,Str "to",Space,Str "that",Space,Str "soul.\""]]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Turn",Space,Str "in",Space,Str "the",Space,Str "door",Space,Str "once",Space,Str "and",Space,Str "turn",Space,Str "once",Space,Str "only"]] [Plain [Str "Turn",Space,Str "in",Space,Str "the",Space,Str "door",Space,Str "once",Space,Str "and",Space,Str "turn",Space,Str "once",Space,Str "only"]]
,Div ("",[],[]) ,Div ("",[],[])
@ -906,25 +906,25 @@
[Div ("",["indent"],[]) [Div ("",["indent"],[])
[Plain [Str "I",Space,Str "sat",Space,Str "upon",Space,Str "the",Space,Str "shore"]] [Plain [Str "I",Space,Str "sat",Space,Str "upon",Space,Str "the",Space,Str "shore"]]
,Div ("wasteland-content.xhtml#ln425",[],[]) ,Div ("wasteland-content.xhtml#ln425",[],[])
[Plain [Str "Fishing,",Space,Str "with",Space,Str "the",Space,Str "arid",Space,Str "plain",Space,Str "behind",Space,Str "me",Note [Para [Link [Str "425."] ("#wasteland-content.xhtml#ln425",""),Space,Str "V.",Space,Str "Weston,",Space,Str "From",Space,Str "Ritual",Space,Str "to",Space,Str "Romance;",Space,Str "chapter",Space,Str "on",Space,Str "the",Space,Str "Fisher",Space,Str "King."]]] [Plain [Str "Fishing,",Space,Str "with",Space,Str "the",Space,Str "arid",Space,Str "plain",Space,Str "behind",Space,Str "me",Note [Para [Link ("",[],[]) [Str "425."] ("#wasteland-content.xhtml#ln425",""),Space,Str "V.",Space,Str "Weston,",Space,Str "From",Space,Str "Ritual",Space,Str "to",Space,Str "Romance;",Space,Str "chapter",Space,Str "on",Space,Str "the",Space,Str "Fisher",Space,Str "King."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "Shall",Space,Str "I",Space,Str "at",Space,Str "least",Space,Str "set",Space,Str "my",Space,Str "lands",Space,Str "in",Space,Str "order?"]] [Plain [Str "Shall",Space,Str "I",Space,Str "at",Space,Str "least",Space,Str "set",Space,Str "my",Space,Str "lands",Space,Str "in",Space,Str "order?"]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "London",Space,Str "Bridge",Space,Str "is",Space,Str "falling",Space,Str "down",Space,Str "falling",Space,Str "down",Space,Str "falling",Space,Str "down"]] [Plain [Str "London",Space,Str "Bridge",Space,Str "is",Space,Str "falling",Space,Str "down",Space,Str "falling",Space,Str "down",Space,Str "falling",Space,Str "down"]]
,Div ("wasteland-content.xhtml#ln428",[],[("lang","it")]) ,Div ("wasteland-content.xhtml#ln428",[],[("lang","it")])
[Plain [Emph [Str "Poi",Space,Str "s'ascose",Space,Str "nel",Space,Str "foco",Space,Str "che",Space,Str "gli",Space,Str "affina"],Space,Note [Para [Link [Str "428."] ("#wasteland-content.xhtml#ln428",""),Space,Str "V.",Space,Str "Purgatorio,",Space,Str "xxvi.",Space,Str "148."],BlockQuote [Para [Str "\"'Ara",Space,Str "vos",Space,Str "prec",Space,Str "per",Space,Str "aquella",Space,Str "valor",LineBreak,Space,Str "'que",Space,Str "vos",Space,Str "guida",Space,Str "al",Space,Str "som",Space,Str "de",Space,Str "l'escalina,",LineBreak,Space,Str "'sovegna",Space,Str "vos",Space,Str "a",Space,Str "temps",Space,Str "de",Space,Str "ma",Space,Str "dolor.'",LineBreak,Space,Str "Poi",Space,Str "s'ascose",Space,Str "nel",Space,Str "foco",Space,Str "che",Space,Str "gli",Space,Str "affina.\""]]]] [Plain [Emph [Str "Poi",Space,Str "s'ascose",Space,Str "nel",Space,Str "foco",Space,Str "che",Space,Str "gli",Space,Str "affina"],Space,Note [Para [Link ("",[],[]) [Str "428."] ("#wasteland-content.xhtml#ln428",""),Space,Str "V.",Space,Str "Purgatorio,",Space,Str "xxvi.",Space,Str "148."],BlockQuote [Para [Str "\"'Ara",Space,Str "vos",Space,Str "prec",Space,Str "per",Space,Str "aquella",Space,Str "valor",LineBreak,Space,Str "'que",Space,Str "vos",Space,Str "guida",Space,Str "al",Space,Str "som",Space,Str "de",Space,Str "l'escalina,",LineBreak,Space,Str "'sovegna",Space,Str "vos",Space,Str "a",Space,Str "temps",Space,Str "de",Space,Str "ma",Space,Str "dolor.'",LineBreak,Space,Str "Poi",Space,Str "s'ascose",Space,Str "nel",Space,Str "foco",Space,Str "che",Space,Str "gli",Space,Str "affina.\""]]]]
,Div ("wasteland-content.xhtml#ln429",[],[]) ,Div ("wasteland-content.xhtml#ln429",[],[])
[Plain [Span ("",[],[("lang","it")]) [Space,Emph [Str "Quando",Space,Str "fiam",Space,Str "ceu",Space,Str "chelidon"],Space],Space,Str "-",Space,Str "O",Space,Str "swallow",Space,Str "swallow",Note [Para [Link [Str "429."] ("#wasteland-content.xhtml#ln429",""),Space,Str "V.",Space,Str "Pervigilium",Space,Str "Veneris.",Space,Str "Cf.",Space,Str "Philomela",Space,Str "in",Space,Str "Parts",Space,Str "II",Space,Str "and",Space,Str "III."]]] [Plain [Span ("",[],[("lang","it")]) [Space,Emph [Str "Quando",Space,Str "fiam",Space,Str "ceu",Space,Str "chelidon"],Space],Space,Str "-",Space,Str "O",Space,Str "swallow",Space,Str "swallow",Note [Para [Link ("",[],[]) [Str "429."] ("#wasteland-content.xhtml#ln429",""),Space,Str "V.",Space,Str "Pervigilium",Space,Str "Veneris.",Space,Str "Cf.",Space,Str "Philomela",Space,Str "in",Space,Str "Parts",Space,Str "II",Space,Str "and",Space,Str "III."]]]
,Div ("wasteland-content.xhtml#ln430",[],[("lang","fr")]) ,Div ("wasteland-content.xhtml#ln430",[],[("lang","fr")])
[Plain [Emph [Str "Le",Space,Str "Prince",Space,Str "d'Aquitaine",Space,Str "a",Space,Str "la",Space,Str "tour",Space,Str "abolie"],Space,Note [Para [Link [Str "430."] ("#wasteland-content.xhtml#ln430",""),Space,Str "V.",Space,Str "Gerard",Space,Str "de",Space,Str "Nerval,",Space,Str "Sonnet",Space,Str "El",Space,Str "Desdichado."]]] [Plain [Emph [Str "Le",Space,Str "Prince",Space,Str "d'Aquitaine",Space,Str "a",Space,Str "la",Space,Str "tour",Space,Str "abolie"],Space,Note [Para [Link ("",[],[]) [Str "430."] ("#wasteland-content.xhtml#ln430",""),Space,Str "V.",Space,Str "Gerard",Space,Str "de",Space,Str "Nerval,",Space,Str "Sonnet",Space,Str "El",Space,Str "Desdichado."]]]
,Div ("",[],[]) ,Div ("",[],[])
[Plain [Str "These",Space,Str "fragments",Space,Str "I",Space,Str "have",Space,Str "shored",Space,Str "against",Space,Str "my",Space,Str "ruins"]] [Plain [Str "These",Space,Str "fragments",Space,Str "I",Space,Str "have",Space,Str "shored",Space,Str "against",Space,Str "my",Space,Str "ruins"]]
,Div ("wasteland-content.xhtml#ln432",[],[]) ,Div ("wasteland-content.xhtml#ln432",[],[])
[Plain [Str "Why",Space,Str "then",Space,Str "Ile",Space,Str "fit",Space,Str "you.",Space,Str "Hieronymo's",Space,Str "mad",Space,Str "againe.",Note [Para [Link [Str "432."] ("#wasteland-content.xhtml#ln432",""),Space,Str "V.",Space,Str "Kyd's",Space,Str "Spanish",Space,Str "Tragedy."]]] [Plain [Str "Why",Space,Str "then",Space,Str "Ile",Space,Str "fit",Space,Str "you.",Space,Str "Hieronymo's",Space,Str "mad",Space,Str "againe.",Note [Para [Link ("",[],[]) [Str "432."] ("#wasteland-content.xhtml#ln432",""),Space,Str "V.",Space,Str "Kyd's",Space,Str "Spanish",Space,Str "Tragedy."]]]
,Div ("",[],[("lang","sa")]) ,Div ("",[],[("lang","sa")])
[Plain [Str "Datta.",Space,Str "Dayadhvam.",Space,Str "Damyata."]] [Plain [Str "Datta.",Space,Str "Dayadhvam.",Space,Str "Damyata."]]
,Div ("wasteland-content.xhtml#ln434",["linegroup","indent"],[]) ,Div ("wasteland-content.xhtml#ln434",["linegroup","indent"],[])
[Plain [Span ("",[],[("lang","sa")]) [Str "Shantih",Space,Str "shantih",Space,Str "shantih",Note [Para [Link [Str "434."] ("#wasteland-content.xhtml#ln434",""),Space,Str "Shantih.",Space,Str "Repeated",Space,Str "as",Space,Str "here,",Space,Str "a",Space,Str "formal",Space,Str "ending",Space,Str "to",Space,Str "an",Space,Str "Upanishad.",Space,Str "'The",Space,Str "Peace",Space,Str "which",Space,Str "passeth",Space,Str "understanding'",Space,Str "is",Space,Str "a",Space,Str "feeble",Space,Str "translation",Space,Str "of",Space,Str "the",Space,Str "content",Space,Str "of",Space,Str "this",Space,Str "word."]]]] [Plain [Span ("",[],[("lang","sa")]) [Str "Shantih",Space,Str "shantih",Space,Str "shantih",Note [Para [Link ("",[],[]) [Str "434."] ("#wasteland-content.xhtml#ln434",""),Space,Str "Shantih.",Space,Str "Repeated",Space,Str "as",Space,Str "here,",Space,Str "a",Space,Str "formal",Space,Str "ending",Space,Str "to",Space,Str "an",Space,Str "Upanishad.",Space,Str "'The",Space,Str "Peace",Space,Str "which",Space,Str "passeth",Space,Str "understanding'",Space,Str "is",Space,Str "a",Space,Str "feeble",Space,Str "translation",Space,Str "of",Space,Str "the",Space,Str "content",Space,Str "of",Space,Str "this",Space,Str "word."]]]]
,Div ("wasteland-content.xhtml#backmatter",["section"],[("type","backmatter")]) ,Div ("wasteland-content.xhtml#backmatter",["section"],[("type","backmatter")])
[Div ("wasteland-content.xhtml#rearnotes",["section"],[("type","rearnotes")]) [Div ("wasteland-content.xhtml#rearnotes",["section"],[("type","rearnotes")])
[Header 2 ("",[],[]) [Str "NOTES",Space,Str "ON",Space,Str "\"THE",Space,Str "WASTE",Space,Str "LAND\""] [Header 2 ("",[],[]) [Str "NOTES",Space,Str "ON",Space,Str "\"THE",Space,Str "WASTE",Space,Str "LAND\""]

View file

@ -1,5 +1,5 @@
Pandoc (Meta {unMeta = fromList []}) Pandoc (Meta {unMeta = fromList []})
[Para [Str "This",Space,Str "file",Space,Str "tests",Space,Str "the",Space,Str "Pandoc",Space,Str "reader",Space,Str "for",Space,Str "Haddock.",Space,Str "We've",Space,Str "borrowed",Space,Str "examples",Space,Str "from",Space,Str "Haddock's",Space,Str "documentation:",Space,Link [Str "http://www.haskell.org/haddock/doc/html/ch03s08.html"] ("http://www.haskell.org/haddock/doc/html/ch03s08.html","http://www.haskell.org/haddock/doc/html/ch03s08.html"),Str "."] [Para [Str "This",Space,Str "file",Space,Str "tests",Space,Str "the",Space,Str "Pandoc",Space,Str "reader",Space,Str "for",Space,Str "Haddock.",Space,Str "We've",Space,Str "borrowed",Space,Str "examples",Space,Str "from",Space,Str "Haddock's",Space,Str "documentation:",Space,Link ("",[],[]) [Str "http://www.haskell.org/haddock/doc/html/ch03s08.html"] ("http://www.haskell.org/haddock/doc/html/ch03s08.html","http://www.haskell.org/haddock/doc/html/ch03s08.html"),Str "."]
,Para [Str "The",Space,Str "following",Space,Str "characters",Space,Str "have",Space,Str "special",Space,Str "meanings",Space,Str "in",Space,Str "Haddock,",Space,Str "/,",Space,Str "',",Space,Str "`,",Space,Str "\",",Space,Str "@,",Space,Str "<,",Space,Str "so",Space,Str "they",Space,Str "must",Space,Str "be",Space,Str "escaped."] ,Para [Str "The",Space,Str "following",Space,Str "characters",Space,Str "have",Space,Str "special",Space,Str "meanings",Space,Str "in",Space,Str "Haddock,",Space,Str "/,",Space,Str "',",Space,Str "`,",Space,Str "\",",Space,Str "@,",Space,Str "<,",Space,Str "so",Space,Str "they",Space,Str "must",Space,Str "be",Space,Str "escaped."]
,Para [Str "*",Space,Str "This",Space,Str "is",Space,Str "a",Space,Str "paragraph,",Space,Str "not",Space,Str "a",Space,Str "list",Space,Str "item.",Space,Str ">",Space,Str "This",Space,Str "sentence",Space,Str "is",Space,Str "not",Space,Str "code.",Space,Str ">>>",Space,Str "This",Space,Str "is",Space,Str "not",Space,Str "an",Space,Str "example."] ,Para [Str "*",Space,Str "This",Space,Str "is",Space,Str "a",Space,Str "paragraph,",Space,Str "not",Space,Str "a",Space,Str "list",Space,Str "item.",Space,Str ">",Space,Str "This",Space,Str "sentence",Space,Str "is",Space,Str "not",Space,Str "code.",Space,Str ">>>",Space,Str "This",Space,Str "is",Space,Str "not",Space,Str "an",Space,Str "example."]
,Para [Str "The",Space,Str "references",Space,Str "\955,",Space,Str "\955",Space,Str "and",Space,Str "\955",Space,Str "all",Space,Str "represent",Space,Str "the",Space,Str "lower-case",Space,Str "letter",Space,Str "lambda."] ,Para [Str "The",Space,Str "references",Space,Str "\955,",Space,Str "\955",Space,Str "and",Space,Str "\955",Space,Str "all",Space,Str "represent",Space,Str "the",Space,Str "lower-case",Space,Str "letter",Space,Str "lambda."]
@ -26,6 +26,6 @@ Pandoc (Meta {unMeta = fromList []})
[[Para [Str "The",Space,Str "description",Space,Str "of",Space,Code ("",[],[]) "foo",Str "."]]]) [[Para [Str "The",Space,Str "description",Space,Str "of",Space,Code ("",[],[]) "foo",Str "."]]])
,([Code ("",[],[]) "bar"], ,([Code ("",[],[]) "bar"],
[[Para [Str "The",Space,Str "description",Space,Str "of",Space,Code ("",[],[]) "bar",Str "."]]])] [[Para [Str "The",Space,Str "description",Space,Str "of",Space,Code ("",[],[]) "bar",Str "."]]])]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "link:",Space,Link [Str "http://haskell.org"] ("http://haskell.org","http://haskell.org")] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "link:",Space,Link ("",[],[]) [Str "http://haskell.org"] ("http://haskell.org","http://haskell.org")]
,Para [Link [Str "Haskell"] ("http://haskell.org","http://haskell.org"),Space,Str "is",Space,Str "a",Space,Str "fun",Space,Str "language!"] ,Para [Link ("",[],[]) [Str "Haskell"] ("http://haskell.org","http://haskell.org"),Space,Str "is",Space,Str "a",Space,Str "fun",Space,Str "language!"]
,Para [Link [Str "Click",Space,Str "Here!"] ("http://example.com","http://example.com")]] ,Para [Link ("",[],[]) [Str "Click",Space,Str "Here!"] ("http://example.com","http://example.com")]]

View file

@ -2,7 +2,7 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber's",Space,Str "markdown",Space,Str "test",Space,Str "suite."] [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber's",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,HorizontalRule ,HorizontalRule
,Header 1 ("headers",[],[]) [Str "Headers"] ,Header 1 ("headers",[],[]) [Str "Headers"]
,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embedded",Space,Str "link"] ("/url","")] ,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link ("",[],[]) [Str "embedded",Space,Str "link"] ("/url","")]
,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]] ,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]]
,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"] ,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"]
,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"] ,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"]
@ -200,7 +200,7 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."] ,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."]
,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."] ,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."]
,Para [Str "Empty",Space,Strong [],Space,Str "and",Space,Emph [],Str "."] ,Para [Str "Empty",Space,Strong [],Space,Str "and",Space,Emph [],Str "."]
,Para [Str "An",Space,Emph [Link [Str "emphasized",Space,Str "link"] ("/url","")],Str "."] ,Para [Str "An",Space,Emph [Link ("",[],[]) [Str "emphasized",Space,Str "link"] ("/url","")],Str "."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]] ,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."] ,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]] ,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
@ -213,7 +213,7 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
,Para [Str "'A',",Space,Str "'B',",Space,Str "and",Space,Str "'C'",Space,Str "are",Space,Str "letters."] ,Para [Str "'A',",Space,Str "'B',",Space,Str "and",Space,Str "'C'",Space,Str "are",Space,Str "letters."]
,Para [Str "'Oak,'",Space,Str "'elm,'",Space,Str "and",Space,Str "'beech'",Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Str "'pine.'"] ,Para [Str "'Oak,'",Space,Str "'elm,'",Space,Str "and",Space,Str "'beech'",Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Str "'pine.'"]
,Para [Str "'He",Space,Str "said,",Space,Str "\"I",Space,Str "want",Space,Str "to",Space,Str "go.\"'",Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70's?"] ,Para [Str "'He",Space,Str "said,",Space,Str "\"I",Space,Str "want",Space,Str "to",Space,Str "go.\"'",Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70's?"]
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Str "'",Code ("",[],[]) "code",Str "'",Space,Str "and",Space,Str "a",Space,Str "\"",Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2",""),Str "\"."] ,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Str "'",Code ("",[],[]) "code",Str "'",Space,Str "and",Space,Str "a",Space,Str "\"",Link ("",[],[]) [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2",""),Str "\"."]
,Para [Str "Some",Space,Str "dashes:",Space,Str "one---two",Space,Str "---",Space,Str "three--four",Space,Str "--",Space,Str "five."] ,Para [Str "Some",Space,Str "dashes:",Space,Str "one---two",Space,Str "---",Space,Str "three--four",Space,Str "--",Space,Str "five."]
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5-7,",Space,Str "255-66,",Space,Str "1987-1999."] ,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5-7,",Space,Str "255-66,",Space,Str "1987-1999."]
,Para [Str "Ellipses...and.",Space,Str ".",Space,Str ".and",Space,Str ".",Space,Str ".",Space,Str ".",Space,Str "."] ,Para [Str "Ellipses...and.",Space,Str ".",Space,Str ".and",Space,Str ".",Space,Str ".",Space,Str ".",Space,Str "."]
@ -269,53 +269,53 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
,HorizontalRule ,HorizontalRule
,Header 1 ("links",[],[]) [Str "Links"] ,Header 1 ("links",[],[]) [Str "Links"]
,Header 2 ("explicit",[],[]) [Str "Explicit"] ,Header 2 ("explicit",[],[]) [Str "Explicit"]
,Para [Str "Just",Space,Str "a",Space,Link [Str "URL"] ("/url/",""),Str "."] ,Para [Str "Just",Space,Str "a",Space,Link ("",[],[]) [Str "URL"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title"),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title"),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by two spaces"),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by two spaces"),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by a tab"),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by a tab"),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with \"quotes\" in it")] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with \"quotes\" in it")]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with single quotes")] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with single quotes")]
,Para [Str "Email",Space,Str "link",Space,Str "(nobody",Space,Str "[at]",Space,Str "nowhere.net)"] ,Para [Str "Email",Space,Str "link",Space,Str "(nobody",Space,Str "[at]",Space,Str "nowhere.net)"]
,Para [Link [Str "Empty"] ("",""),Str "."] ,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."]
,Header 2 ("reference",[],[]) [Str "Reference"] ,Header 2 ("reference",[],[]) [Str "Reference"]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "With",Space,Link [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."] ,Para [Str "With",Space,Link ("",[],[]) [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."]
,Para [Link [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."] ,Para [Link ("",[],[]) [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."]
,Para [Str "Indented",Space,Link [Str "once"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "once"] ("/url",""),Str "."]
,Para [Str "Indented",Space,Link [Str "twice"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "twice"] ("/url",""),Str "."]
,Para [Str "Indented",Space,Link [Str "thrice"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "thrice"] ("/url",""),Str "."]
,Para [Str "This",Space,Str "should",Space,Str "[not]",Space,Str "be",Space,Str "a",Space,Str "link."] ,Para [Str "This",Space,Str "should",Space,Str "[not]",Space,Str "be",Space,Str "a",Space,Str "link."]
,CodeBlock ("",[],[]) "[not]: /url" ,CodeBlock ("",[],[]) "[not]: /url"
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/","Title with \"quotes\" inside"),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/","Title with \"quotes\" inside"),Str "."]
,Para [Str "Foo",Space,Link [Str "biz"] ("/url/","Title with \"quote\" inside"),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "biz"] ("/url/","Title with \"quote\" inside"),Str "."]
,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"] ,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"]
,Para [Str "Here's",Space,Str "a",Space,Link [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."] ,Para [Str "Here's",Space,Str "a",Space,Link ("",[],[]) [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
,Para [Str "Here's",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link [Str "AT&T"] ("http://att.com/","AT&T"),Str "."] ,Para [Str "Here's",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link ("",[],[]) [Str "AT&T"] ("http://att.com/","AT&T"),Str "."]
,Para [Str "Here's",Space,Str "an",Space,Link [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."] ,Para [Str "Here's",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
,Para [Str "Here's",Space,Str "an",Space,Link [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."] ,Para [Str "Here's",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."]
,Header 2 ("autolinks",[],[]) [Str "Autolinks"] ,Header 2 ("autolinks",[],[]) [Str "Autolinks"]
,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")] ,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link ("",[],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
,BulletList ,BulletList
[[Plain [Str "In",Space,Str "a",Space,Str "list?"]] [[Plain [Str "In",Space,Str "a",Space,Str "list?"]]
,[Plain [Link [Str "http://example.com/"] ("http://example.com/","")]] ,[Plain [Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
,[Plain [Str "It",Space,Str "should."]]] ,[Plain [Str "It",Space,Str "should."]]]
,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Str "nobody",Space,Str "[at]",Space,Str "nowhere.net"] ,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Str "nobody",Space,Str "[at]",Space,Str "nowhere.net"]
,BlockQuote ,BlockQuote
[Para [Str "Blockquoted:",Space,Link [Str "http://example.com/"] ("http://example.com/","")]] [Para [Str "Blockquoted:",Space,Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"] ,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"]
,CodeBlock ("",[],[]) "or here: <http://example.com/>" ,CodeBlock ("",[],[]) "or here: <http://example.com/>"
,HorizontalRule ,HorizontalRule
,Header 1 ("images",[],[]) [Str "Images"] ,Header 1 ("images",[],[]) [Str "Images"]
,Para [Str "From",Space,Str "\"Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune\"",Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"] ,Para [Str "From",Space,Str "\"Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune\"",Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
,Para [Image [Str "lalune"] ("lalune.jpg","Voyage dans la Lune")] ,Para [Image ("",[],[]) [Str "lalune"] ("lalune.jpg","Voyage dans la Lune")]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon."] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [Str "movie"] ("movie.jpg",""),Space,Str "icon."]
,HorizontalRule ,HorizontalRule
,Header 1 ("footnotes",[],[]) [Str "Footnotes"] ,Header 1 ("footnotes",[],[]) [Str "Footnotes"]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",Link [Str "(1)"] ("#note_1",""),Str ",",Space,Str "and",Space,Str "another",Link [Str "(longnote)"] ("#note_longnote",""),Str ".",Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space^(my",Space,Str "note)."] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference",Link ("",[],[]) [Str "(1)"] ("#note_1",""),Str ",",Space,Str "and",Space,Str "another",Link ("",[],[]) [Str "(longnote)"] ("#note_longnote",""),Str ".",Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space^(my",Space,Str "note)."]
,Para [Link [Str "(1)"] ("#ref_1",""),Space,Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "in",Space,Str "the",Space,Str "document,",Space,Str "not",Space,Str "just",Space,Str "at",Space,Str "the",Space,Str "end."] ,Para [Link ("",[],[]) [Str "(1)"] ("#ref_1",""),Space,Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "in",Space,Str "the",Space,Str "document,",Space,Str "not",Space,Str "just",Space,Str "at",Space,Str "the",Space,Str "end."]
,Para [Link [Str "(longnote)"] ("#ref_longnote",""),Space,Str "Here's",Space,Str "the",Space,Str "other",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."] ,Para [Link ("",[],[]) [Str "(longnote)"] ("#ref_longnote",""),Space,Str "Here's",Space,Str "the",Space,Str "other",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."]
,Para [Str "Caret",Space,Str "characters",Space,Str "are",Space,Str "used",Space,Str "to",Space,Str "indicate",Space,Str "that",Space,Str "the",Space,Str "blocks",Space,Str "all",Space,Str "belong",Space,Str "to",Space,Str "a",Space,Str "single",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "block",Space,Str "quotes)."] ,Para [Str "Caret",Space,Str "characters",Space,Str "are",Space,Str "used",Space,Str "to",Space,Str "indicate",Space,Str "that",Space,Str "the",Space,Str "blocks",Space,Str "all",Space,Str "belong",Space,Str "to",Space,Str "a",Space,Str "single",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "block",Space,Str "quotes)."]
,CodeBlock ("",[],[]) " { <code> }" ,CodeBlock ("",[],[]) " { <code> }"
,Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "use",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "every",Space,Str "line,",Space,Str "as",Space,Str "with",Space,Str "blockquotes,",Space,Str "but",Space,Str "all",Space,Str "that",Space,Str "you",Space,Str "need",Space,Str "is",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "the",Space,Str "block",Space,Str "and",Space,Str "any",Space,Str "preceding",Space,Str "blank",Space,Str "lines."] ,Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "use",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "every",Space,Str "line,",Space,Str "as",Space,Str "with",Space,Str "blockquotes,",Space,Str "but",Space,Str "all",Space,Str "that",Space,Str "you",Space,Str "need",Space,Str "is",Space,Str "a",Space,Str "caret",Space,Str "at",Space,Str "the",Space,Str "beginning",Space,Str "of",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "the",Space,Str "block",Space,Str "and",Space,Str "any",Space,Str "preceding",Space,Str "blank",Space,Str "lines."]

View file

@ -845,31 +845,4 @@ indented.
\$ \% \& \# \_ \{ \} \$ \% \& \# \_ \{ \}
\section{Block newcommands}
See e.g. issues #1866, #1835
\newcommand{\FIG}[3]{
\begin{figure}[h!]
\centering
\includegraphics[width=#2\columnwidth,angle=0]{#1}
\caption{#3}
\label{fig:#1}
\end{figure}
}
\newcommand{\separator}{\vspace{4em}}
\separator
\FIG{lalune.jpg}{0.5}{Test caption}
\newcommand{\wbal}{The Wikibook about \LaTeX}
\wbal is a good resource for learning \LaTeX.
\separator with trailing inlines
\FIG{lalune.jpg}{0.5}{Test caption} with trailing inlines
\end{document} \end{document}

View file

@ -3,7 +3,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."] ,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,HorizontalRule ,HorizontalRule
,Header 1 ("headers",[],[]) [Str "Headers"] ,Header 1 ("headers",[],[]) [Str "Headers"]
,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embedded",Space,Str "link"] ("/url","")] ,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link ("",[],[]) [Str "embedded",Space,Str "link"] ("/url","")]
,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]] ,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]]
,Para [Str "Level",Space,Str "4"] ,Para [Str "Level",Space,Str "4"]
,Para [Str "Level",Space,Str "5"] ,Para [Str "Level",Space,Str "5"]
@ -237,7 +237,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"] ,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"]
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."] ,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."]
,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."] ,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."]
,Para [Str "An",Space,Emph [Link [Str "emphasized",Space,Str "link"] ("/url","")],Str "."] ,Para [Str "An",Space,Emph [Link ("",[],[]) [Str "emphasized",Space,Str "link"] ("/url","")],Str "."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]] ,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."] ,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]] ,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
@ -253,7 +253,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters."] ,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters."]
,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]] ,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]]
,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70\8217s?"] ,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70\8217s?"]
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."] ,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link ("",[],[]) [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."]
,Para [Str "Some",Space,Str "dashes:",Space,Str "one\8212two\8212three\8212four\8212five."] ,Para [Str "Some",Space,Str "dashes:",Space,Str "one\8212two\8212three\8212four\8212five."]
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5\8211\&7,",Space,Str "255\8211\&66,",Space,Str "1987\8211\&1999."] ,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5\8211\&7,",Space,Str "255\8211\&66,",Space,Str "1987\8211\&1999."]
,Para [Str "Ellipses\8230and\8230and\8230."] ,Para [Str "Ellipses\8230and\8230and\8230."]
@ -320,65 +320,56 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,HorizontalRule ,HorizontalRule
,Header 1 ("links",[],[]) [Str "Links"] ,Header 1 ("links",[],[]) [Str "Links"]
,Header 2 ("explicit",[],[]) [Str "Explicit"] ,Header 2 ("explicit",[],[]) [Str "Explicit"]
,Para [Str "Just",Space,Str "a",Space,Link [Str "URL"] ("/url/",""),Str "."] ,Para [Str "Just",Space,Str "a",Space,Link ("",[],[]) [Str "URL"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","")] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","")]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","")] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","")]
,Para [Link [Str "with_underscore"] ("/url/with_underscore","")] ,Para [Link ("",[],[]) [Str "with_underscore"] ("/url/with_underscore","")]
,Para [Link [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")] ,Para [Link ("",[],[]) [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")]
,Para [Link [Str "Empty"] ("",""),Str "."] ,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."]
,Header 2 ("reference",[],[]) [Str "Reference"] ,Header 2 ("reference",[],[]) [Str "Reference"]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "With",Space,Link [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."] ,Para [Str "With",Space,Link ("",[],[]) [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."]
,Para [Link [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."] ,Para [Link ("",[],[]) [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."]
,Para [Str "Indented",Space,Link [Str "once"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "once"] ("/url",""),Str "."]
,Para [Str "Indented",Space,Link [Str "twice"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "twice"] ("/url",""),Str "."]
,Para [Str "Indented",Space,Link [Str "thrice"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "thrice"] ("/url",""),Str "."]
,Para [Str "This",Space,Str "should",Space,Str "[not][]",Space,Str "be",Space,Str "a",Space,Str "link."] ,Para [Str "This",Space,Str "should",Space,Str "[not][]",Space,Str "be",Space,Str "a",Space,Str "link."]
,CodeBlock ("",[],[]) "[not]: /url" ,CodeBlock ("",[],[]) "[not]: /url"
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "biz"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "biz"] ("/url/",""),Str "."]
,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"] ,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"]
,Para [Str "Here\8217s",Space,Str "a",Space,Link [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "a",Space,Link ("",[],[]) [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link [Str "AT&T"] ("http://att.com/",""),Str "."] ,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link ("",[],[]) [Str "AT&T"] ("http://att.com/",""),Str "."]
,Para [Str "Here\8217s",Space,Str "an",Space,Link [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
,Para [Str "Here\8217s",Space,Str "an",Space,Link [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."]
,Header 2 ("autolinks",[],[]) [Str "Autolinks"] ,Header 2 ("autolinks",[],[]) [Str "Autolinks"]
,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")] ,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link ("",[],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
,BulletList ,BulletList
[[Para [Str "In",Space,Str "a",Space,Str "list?"]] [[Para [Str "In",Space,Str "a",Space,Str "list?"]]
,[Para [Link [Str "http://example.com/"] ("http://example.com/","")]] ,[Para [Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
,[Para [Str "It",Space,Str "should."]]] ,[Para [Str "It",Space,Str "should."]]]
,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")] ,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",[],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
,BlockQuote ,BlockQuote
[Para [Str "Blockquoted:",Space,Link [Str "http://example.com/"] ("http://example.com/","")]] [Para [Str "Blockquoted:",Space,Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"] ,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"]
,CodeBlock ("",[],[]) "or here: <http://example.com/>" ,CodeBlock ("",[],[]) "or here: <http://example.com/>"
,HorizontalRule ,HorizontalRule
,Header 1 ("images",[],[]) [Str "Images"] ,Header 1 ("images",[],[]) [Str "Images"]
,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"] ,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
,Para [Image [Str "image"] ("lalune.jpg","")] ,Para [Image ("",[],[]) [Str "image"] ("lalune.jpg","")]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "image"] ("movie.jpg",""),Space,Str "icon."] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [Str "image"] ("movie.jpg",""),Space,Str "icon."]
,HorizontalRule ,HorizontalRule
,Header 1 ("footnotes",[],[]) [Str "Footnotes"] ,Header 1 ("footnotes",[],[]) [Str "Footnotes"]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link ("",[],[]) [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]]
,BlockQuote ,BlockQuote
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]] [Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]]
,OrderedList (1,Decimal,Period) ,OrderedList (1,Decimal,Period)
[[Para [Str "And",Space,Str "in",Space,Str "list",Space,Str "items.",Note [Para [Str "In",Space,Str "list."]]]]] [[Para [Str "And",Space,Str "in",Space,Str "list",Space,Str "items.",Note [Para [Str "In",Space,Str "list."]]]]]
,Para [Str "This",Space,Str "paragraph",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "part",Space,Str "of",Space,Str "the",Space,Str "note,",Space,Str "as",Space,Str "it",Space,Str "is",Space,Str "not",Space,Str "indented."] ,Para [Str "This",Space,Str "paragraph",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "part",Space,Str "of",Space,Str "the",Space,Str "note,",Space,Str "as",Space,Str "it",Space,Str "is",Space,Str "not",Space,Str "indented."]
,Header 1 ("escaped-characters",[],[]) [Str "Escaped",Space,Str "characters"] ,Header 1 ("escaped-characters",[],[]) [Str "Escaped",Space,Str "characters"]
,Para [Str "$",Space,Str "%",Space,Str "&",Space,Str "#",Space,Str "_",Space,Str "{",Space,Str "}"] ,Para [Str "$",Space,Str "%",Space,Str "&",Space,Str "#",Space,Str "_",Space,Str "{",Space,Str "}"]]
,Header 1 ("block-newcommands",[],[]) [Str "Block",Space,Str "newcommands"]
,Para [Str "See",Space,Str "e.g.",Space,Str "issues",Space,Str "#1866,",Space,Str "#1835"]
,RawBlock (Format "latex") "\\vspace{4em}"
,Para [RawInline (Format "latex") "\\centering",Image [Str "Test",Space,Str "caption",Span ("",[],[("data-label","fig:lalune.jpg")]) []] ("lalune.jpg","fig:")]
,Para [Span ("",[],[]) [Str "The",Space,Str "Wikibook",Space,Str "about",Space,Str "LaTeX"],Str "is",Space,Str "a",Space,Str "good",Space,Str "resource",Space,Str "for",Space,Str "learning",Space,Str "LaTeX."]
,RawBlock (Format "latex") "\\vspace{4em}"
,Para [Str "with",Space,Str "trailing",Space,Str "inlines"]
,Para [RawInline (Format "latex") "\\centering",Image [Str "Test",Space,Str "caption",Span ("",[],[("data-label","fig:lalune.jpg")]) []] ("lalune.jpg","fig:")]
,Para [Str "with",Space,Str "trailing",Space,Str "inlines"]]

View file

@ -1,14 +1,14 @@
[Header 1 ("additional-markdown-reader-tests",[],[]) [Str "Additional",Space,Str "markdown",Space,Str "reader",Space,Str "tests"] [Header 1 ("additional-markdown-reader-tests",[],[]) [Str "Additional",Space,Str "markdown",Space,Str "reader",Space,Str "tests"]
,Header 2 ("blank-line-before-url-in-link-reference",[],[]) [Str "Blank",Space,Str "line",Space,Str "before",Space,Str "URL",Space,Str "in",Space,Str "link",Space,Str "reference"] ,Header 2 ("blank-line-before-url-in-link-reference",[],[]) [Str "Blank",Space,Str "line",Space,Str "before",Space,Str "URL",Space,Str "in",Space,Str "link",Space,Str "reference"]
,Para [Link [Str "foo"] ("/url",""),Space,Str "and",Space,Link [Str "bar"] ("/url","title")] ,Para [Link ("",[],[]) [Str "foo"] ("/url",""),Space,Str "and",Space,Link ("",[],[]) [Str "bar"] ("/url","title")]
,Header 2 ("raw-context-environments",[],[]) [Str "Raw",Space,Str "ConTeXt",Space,Str "environments"] ,Header 2 ("raw-context-environments",[],[]) [Str "Raw",Space,Str "ConTeXt",Space,Str "environments"]
,Plain [RawInline (Format "tex") "\\placeformula "] ,Plain [RawInline (Format "tex") "\\placeformula "]
,RawBlock (Format "context") "\\startformula\n L_{1} = L_{2}\n \\stopformula" ,RawBlock (Format "context") "\\startformula\n L_{1} = L_{2}\n \\stopformula"
,RawBlock (Format "context") "\\start[a2]\n\\start[a2]\n\\stop[a2]\n\\stop[a2]" ,RawBlock (Format "context") "\\start[a2]\n\\start[a2]\n\\stop[a2]\n\\stop[a2]"
,Header 2 ("urls-with-spaces-and-punctuation",[],[]) [Str "URLs",Space,Str "with",Space,Str "spaces",Space,Str "and",Space,Str "punctuation"] ,Header 2 ("urls-with-spaces-and-punctuation",[],[]) [Str "URLs",Space,Str "with",Space,Str "spaces",Space,Str "and",Space,Str "punctuation"]
,Para [Link [Str "foo"] ("/bar%20and%20baz",""),Space,Link [Str "foo"] ("/bar%20and%20baz",""),Space,Link [Str "foo"] ("/bar%20and%20baz",""),Space,Link [Str "foo"] ("bar%20baz","title")] ,Para [Link ("",[],[]) [Str "foo"] ("/bar%20and%20baz",""),Space,Link ("",[],[]) [Str "foo"] ("/bar%20and%20baz",""),Space,Link ("",[],[]) [Str "foo"] ("/bar%20and%20baz",""),Space,Link ("",[],[]) [Str "foo"] ("bar%20baz","title")]
,Para [Link [Str "baz"] ("/foo%20foo",""),Space,Link [Str "bam"] ("/foo%20fee",""),Space,Link [Str "bork"] ("/foo/zee%20zob","title")] ,Para [Link ("",[],[]) [Str "baz"] ("/foo%20foo",""),Space,Link ("",[],[]) [Str "bam"] ("/foo%20fee",""),Space,Link ("",[],[]) [Str "bork"] ("/foo/zee%20zob","title")]
,Para [Link [Str "Ward\8217s",Space,Str "method."] ("http://en.wikipedia.org/wiki/Ward's_method","")] ,Para [Link ("",[],[]) [Str "Ward\8217s",Space,Str "method."] ("http://en.wikipedia.org/wiki/Ward's_method","")]
,Header 2 ("horizontal-rules-with-spaces-at-end",[],[]) [Str "Horizontal",Space,Str "rules",Space,Str "with",Space,Str "spaces",Space,Str "at",Space,Str "end"] ,Header 2 ("horizontal-rules-with-spaces-at-end",[],[]) [Str "Horizontal",Space,Str "rules",Space,Str "with",Space,Str "spaces",Space,Str "at",Space,Str "end"]
,HorizontalRule ,HorizontalRule
,HorizontalRule ,HorizontalRule
@ -42,9 +42,9 @@
,Para [Str "`hi"] ,Para [Str "`hi"]
,Para [Str "there`"] ,Para [Str "there`"]
,Header 2 ("multilingual-urls",[],[]) [Str "Multilingual",Space,Str "URLs"] ,Header 2 ("multilingual-urls",[],[]) [Str "Multilingual",Space,Str "URLs"]
,Para [Link [Str "http://\27979.com?\27979=\27979"] ("http://\27979.com?\27979=\27979","")] ,Para [Link ("",[],[]) [Str "http://\27979.com?\27979=\27979"] ("http://\27979.com?\27979=\27979","")]
,Para [Link [Str "foo"] ("/bar/\27979?x=\27979","title")] ,Para [Link ("",[],[]) [Str "foo"] ("/bar/\27979?x=\27979","title")]
,Para [Link [Str "\27979@foo.\27979.baz"] ("mailto:\27979@foo.\27979.baz","")] ,Para [Link ("",[],[]) [Str "\27979@foo.\27979.baz"] ("mailto:\27979@foo.\27979.baz","")]
,Header 2 ("numbered-examples",[],[]) [Str "Numbered",Space,Str "examples"] ,Header 2 ("numbered-examples",[],[]) [Str "Numbered",Space,Str "examples"]
,OrderedList (1,Example,TwoParens) ,OrderedList (1,Example,TwoParens)
[[Plain [Str "First",Space,Str "example."]] [[Plain [Str "First",Space,Str "example."]]
@ -55,9 +55,9 @@
,Header 2 ("macros",[],[]) [Str "Macros"] ,Header 2 ("macros",[],[]) [Str "Macros"]
,Para [Math InlineMath "{\\langle x,y \\rangle}"] ,Para [Math InlineMath "{\\langle x,y \\rangle}"]
,Header 2 ("case-insensitive-references",[],[]) [Str "Case-insensitive",Space,Str "references"] ,Header 2 ("case-insensitive-references",[],[]) [Str "Case-insensitive",Space,Str "references"]
,Para [Link [Str "Fum"] ("/fum","")] ,Para [Link ("",[],[]) [Str "Fum"] ("/fum","")]
,Para [Link [Str "FUM"] ("/fum","")] ,Para [Link ("",[],[]) [Str "FUM"] ("/fum","")]
,Para [Link [Str "bat"] ("/bat","")] ,Para [Link ("",[],[]) [Str "bat"] ("/bat","")]
,Header 2 ("curly-smart-quotes",[],[]) [Str "Curly",Space,Str "smart",Space,Str "quotes"] ,Header 2 ("curly-smart-quotes",[],[]) [Str "Curly",Space,Str "smart",Space,Str "quotes"]
,Para [Quoted DoubleQuote [Str "Hi"]] ,Para [Quoted DoubleQuote [Str "Hi"]]
,Para [Quoted SingleQuote [Str "Hi"]] ,Para [Quoted SingleQuote [Str "Hi"]]
@ -74,11 +74,11 @@
,Header 2 ("implicit-header-references",[],[]) [Str "Implicit",Space,Str "header",Space,Str "references"] ,Header 2 ("implicit-header-references",[],[]) [Str "Implicit",Space,Str "header",Space,Str "references"]
,Header 3 ("my-header-1",[],[]) [Str "My",Space,Str "header"] ,Header 3 ("my-header-1",[],[]) [Str "My",Space,Str "header"]
,Header 3 ("my-other-header",[],[]) [Str "My",Space,Str "other",Space,Str "header"] ,Header 3 ("my-other-header",[],[]) [Str "My",Space,Str "other",Space,Str "header"]
,Para [Str "A",Space,Str "link",Space,Str "to",Space,Link [Str "My",Space,Str "header"] ("#my-header-1",""),Str "."] ,Para [Str "A",Space,Str "link",Space,Str "to",Space,Link ("",[],[]) [Str "My",Space,Str "header"] ("#my-header-1",""),Str "."]
,Para [Str "Another",Space,Str "link",Space,Str "to",Space,Link [Str "it"] ("#my-header-1",""),Str "."] ,Para [Str "Another",Space,Str "link",Space,Str "to",Space,Link ("",[],[]) [Str "it"] ("#my-header-1",""),Str "."]
,Para [Str "Should",Space,Str "be",Space,Link [Str "case",Space,Str "insensitive"] ("#my-header-1",""),Str "."] ,Para [Str "Should",Space,Str "be",Space,Link ("",[],[]) [Str "case",Space,Str "insensitive"] ("#my-header-1",""),Str "."]
,Para [Str "Link",Space,Str "to",Space,Link [Str "Explicit",Space,Str "header",Space,Str "attributes"] ("#foobar",""),Str "."] ,Para [Str "Link",Space,Str "to",Space,Link ("",[],[]) [Str "Explicit",Space,Str "header",Space,Str "attributes"] ("#foobar",""),Str "."]
,Para [Str "But",Space,Str "this",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "link",Space,Str "to",Space,Link [Str "My",Space,Str "other",Space,Str "header"] ("/foo",""),Str ",",Space,Str "since",Space,Str "the",Space,Str "reference",Space,Str "is",Space,Str "defined."] ,Para [Str "But",Space,Str "this",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "link",Space,Str "to",Space,Link ("",[],[]) [Str "My",Space,Str "other",Space,Str "header"] ("/foo",""),Str ",",Space,Str "since",Space,Str "the",Space,Str "reference",Space,Str "is",Space,Str "defined."]
,Header 2 ("foobar",["baz"],[("key","val")]) [Str "Explicit",Space,Str "header",Space,Str "attributes"] ,Header 2 ("foobar",["baz"],[("key","val")]) [Str "Explicit",Space,Str "header",Space,Str "attributes"]
,BlockQuote ,BlockQuote
[Header 2 ("foobar",["baz"],[("key","val")]) [Str "Header",Space,Str "attributes",Space,Str "inside",Space,Str "block",Space,Str "quote"]] [Header 2 ("foobar",["baz"],[("key","val")]) [Str "Header",Space,Str "attributes",Space,Str "inside",Space,Str "block",Space,Str "quote"]]
@ -143,23 +143,23 @@
[[[] [[[]
,[]]] ,[]]]
,Header 2 ("entities-in-links-and-titles",[],[]) [Str "Entities",Space,Str "in",Space,Str "links",Space,Str "and",Space,Str "titles"] ,Header 2 ("entities-in-links-and-titles",[],[]) [Str "Entities",Space,Str "in",Space,Str "links",Space,Str "and",Space,Str "titles"]
,Para [Link [Str "link"] ("/\252rl","\246\246!")] ,Para [Link ("",[],[]) [Str "link"] ("/\252rl","\246\246!")]
,Para [Link [Str "http://g\246\246gle.com"] ("http://g\246\246gle.com","")] ,Para [Link ("",[],[]) [Str "http://g\246\246gle.com"] ("http://g\246\246gle.com","")]
,Para [Link [Str "me@ex\228mple.com"] ("mailto:me@ex\228mple.com","")] ,Para [Link ("",[],[]) [Str "me@ex\228mple.com"] ("mailto:me@ex\228mple.com","")]
,Para [Link [Str "foobar"] ("/\252rl","\246\246!")] ,Para [Link ("",[],[]) [Str "foobar"] ("/\252rl","\246\246!")]
,Header 2 ("parentheses-in-urls",[],[]) [Str "Parentheses",Space,Str "in",Space,Str "URLs"] ,Header 2 ("parentheses-in-urls",[],[]) [Str "Parentheses",Space,Str "in",Space,Str "URLs"]
,Para [Link [Str "link"] ("/hi(there)","")] ,Para [Link ("",[],[]) [Str "link"] ("/hi(there)","")]
,Para [Link [Str "link"] ("/hithere)","")] ,Para [Link ("",[],[]) [Str "link"] ("/hithere)","")]
,Para [Link [Str "linky"] ("hi_(there_(nested))","")] ,Para [Link ("",[],[]) [Str "linky"] ("hi_(there_(nested))","")]
,Header 2 ("backslashes-in-link-references",[],[]) [Str "Backslashes",Space,Str "in",Space,Str "link",Space,Str "references"] ,Header 2 ("backslashes-in-link-references",[],[]) [Str "Backslashes",Space,Str "in",Space,Str "link",Space,Str "references"]
,Para [Link [Str "*",RawInline (Format "tex") "\\a"] ("b","")] ,Para [Link ("",[],[]) [Str "*",RawInline (Format "tex") "\\a"] ("b","")]
,Header 2 ("reference-link-fallbacks",[],[]) [Str "Reference",Space,Str "link",Space,Str "fallbacks"] ,Header 2 ("reference-link-fallbacks",[],[]) [Str "Reference",Space,Str "link",Space,Str "fallbacks"]
,Para [Str "[",Emph [Str "not",Space,Str "a",Space,Str "link"],Str "]",Space,Str "[",Emph [Str "nope"],Str "]\8230"] ,Para [Str "[",Emph [Str "not",Space,Str "a",Space,Str "link"],Str "]",Space,Str "[",Emph [Str "nope"],Str "]\8230"]
,Header 2 ("reference-link-followed-by-a-citation",[],[]) [Str "Reference",Space,Str "link",Space,Str "followed",Space,Str "by",Space,Str "a",Space,Str "citation"] ,Header 2 ("reference-link-followed-by-a-citation",[],[]) [Str "Reference",Space,Str "link",Space,Str "followed",Space,Str "by",Space,Str "a",Space,Str "citation"]
,Para [Str "MapReduce",Space,Str "is",Space,Str "a",Space,Str "paradigm",Space,Str "popularized",Space,Str "by",Space,Link [Str "Google"] ("http://google.com",""),Space,Cite [Citation {citationId = "mapreduce", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@mapreduce]"],Space,Str "as",Space,Str "its",Space,Str "most",Space,Str "vocal",Space,Str "proponent."] ,Para [Str "MapReduce",Space,Str "is",Space,Str "a",Space,Str "paradigm",Space,Str "popularized",Space,Str "by",Space,Link ("",[],[]) [Str "Google"] ("http://google.com",""),Space,Cite [Citation {citationId = "mapreduce", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@mapreduce]"],Space,Str "as",Space,Str "its",Space,Str "most",Space,Str "vocal",Space,Str "proponent."]
,Header 2 ("empty-reference-links",[],[]) [Str "Empty",Space,Str "reference",Space,Str "links"] ,Header 2 ("empty-reference-links",[],[]) [Str "Empty",Space,Str "reference",Space,Str "links"]
,Para [Str "bar"] ,Para [Str "bar"]
,Para [Link [Str "foo2"] ("","")] ,Para [Link ("",[],[]) [Str "foo2"] ("","")]
,Header 2 ("wrapping-shouldnt-introduce-new-list-items",[],[]) [Str "Wrapping",Space,Str "shouldn\8217t",Space,Str "introduce",Space,Str "new",Space,Str "list",Space,Str "items"] ,Header 2 ("wrapping-shouldnt-introduce-new-list-items",[],[]) [Str "Wrapping",Space,Str "shouldn\8217t",Space,Str "introduce",Space,Str "new",Space,Str "list",Space,Str "items"]
,BulletList ,BulletList
[[Plain [Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "2015."]]]] [[Plain [Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "blah",Space,Str "2015."]]]]

View file

@ -71,24 +71,26 @@ Pandoc (Meta {unMeta = fromList []})
,Para [Str "With",Space,Str "two",Space,Str "paragraphs."]] ,Para [Str "With",Space,Str "two",Space,Str "paragraphs."]]
,Para [Str "Nother",Space,Str "paragraph."] ,Para [Str "Nother",Space,Str "paragraph."]
,Header 2 ("external-links",[],[]) [Str "external",Space,Str "links"] ,Header 2 ("external-links",[],[]) [Str "external",Space,Str "links"]
,Para [Link [Emph [Str "Google"],Space,Str "search",Space,Str "engine"] ("http://google.com","")] ,Para [Link ("",[],[]) [Emph [Str "Google"],Space,Str "search",Space,Str "engine"] ("http://google.com","")]
,Para [Link [Str "http://pandoc.org"] ("http://pandoc.org","")] ,Para [Link ("",[],[]) [Str "http://pandoc.org"] ("http://pandoc.org","")]
,Para [Link [Str "1"] ("http://google.com",""),Space,Link [Str "2"] ("http://yahoo.com","")] ,Para [Link ("",[],[]) [Str "1"] ("http://google.com",""),Space,Link ("",[],[]) [Str "2"] ("http://yahoo.com","")]
,Para [Link [Str "email",Space,Str "me"] ("mailto:info@example.org","")] ,Para [Link ("",[],[]) [Str "email",Space,Str "me"] ("mailto:info@example.org","")]
,Header 2 ("internal-links",[],[]) [Str "internal",Space,Str "links"] ,Header 2 ("internal-links",[],[]) [Str "internal",Space,Str "links"]
,Para [Link [Str "Help"] ("Help","wikilink")] ,Para [Link ("",[],[]) [Str "Help"] ("Help","wikilink")]
,Para [Link [Str "the",Space,Str "help",Space,Str "page"] ("Help","wikilink")] ,Para [Link ("",[],[]) [Str "the",Space,Str "help",Space,Str "page"] ("Help","wikilink")]
,Para [Link [Str "Helpers"] ("Help","wikilink")] ,Para [Link ("",[],[]) [Str "Helpers"] ("Help","wikilink")]
,Para [Link [Str "Help"] ("Help","wikilink"),Str "ers"] ,Para [Link ("",[],[]) [Str "Help"] ("Help","wikilink"),Str "ers"]
,Para [Link [Str "Contents"] ("Help:Contents","wikilink")] ,Para [Link ("",[],[]) [Str "Contents"] ("Help:Contents","wikilink")]
,Para [Link [Str "#My",Space,Str "anchor"] ("#My_anchor","wikilink")] ,Para [Link ("",[],[]) [Str "#My",Space,Str "anchor"] ("#My_anchor","wikilink")]
,Para [Link [Str "and",Space,Str "text"] ("Page#with_anchor","wikilink")] ,Para [Link ("",[],[]) [Str "and",Space,Str "text"] ("Page#with_anchor","wikilink")]
,Header 2 ("images",[],[]) [Str "images"] ,Header 2 ("images",[],[]) [Str "images"]
,Para [Image [Str "caption"] ("example.jpg","fig:caption")] ,Para [Image ("",[],[]) [Str "caption"] ("example.jpg","fig:caption")]
,Para [Image [Str "the",Space,Emph [Str "caption"],Space,Str "with",Space,Link [Str "external",Space,Str "link"] ("http://google.com","")] ("example.jpg","fig:the caption with external link")] ,Para [Image ("",[],[]) [Str "the",Space,Emph [Str "caption"],Space,Str "with",Space,Link ("",[],[]) [Str "external",Space,Str "link"] ("http://google.com","")] ("example.jpg","fig:the caption with external link")]
,Para [Image [Str "caption"] ("example.jpg","fig:caption")] ,Para [Image ("",[],[("width","30"),("height","40")]) [Str "caption"] ("example.jpg","fig:caption")]
,Para [Image [Str "example.jpg"] ("example.jpg","fig:example.jpg")] ,Para [Image ("",[],[("width","30")]) [Str "caption"] ("example.jpg","fig:caption")]
,Para [Image [Str "example_es.jpg"] ("example_es.jpg","fig:example_es.jpg")] ,Para [Image ("",[],[("width","30")]) [Str "caption"] ("example.jpg","fig:caption")]
,Para [Image ("",[],[]) [Str "example.jpg"] ("example.jpg","fig:example.jpg")]
,Para [Image ("",[],[]) [Str "example_es.jpg"] ("example_es.jpg","fig:example_es.jpg")]
,Header 2 ("lists",[],[]) [Str "lists"] ,Header 2 ("lists",[],[]) [Str "lists"]
,BulletList ,BulletList
[[Plain [Str "Start",Space,Str "each",Space,Str "line"]] [[Plain [Str "Start",Space,Str "each",Space,Str "line"]]
@ -252,4 +254,4 @@ Pandoc (Meta {unMeta = fromList []})
,Para [Str "Paragraph",Space,Str "after",Space,Str "the",Space,Str "table."] ,Para [Str "Paragraph",Space,Str "after",Space,Str "the",Space,Str "table."]
,Header 2 ("notes",[],[]) [Str "notes"] ,Header 2 ("notes",[],[]) [Str "notes"]
,Para [Str "My",Space,Str "note!",Note [Plain [Str "This."]]] ,Para [Str "My",Space,Str "note!",Note [Plain [Str "This."]]]
,Para [Str "URL",Space,Str "note.",Note [Plain [Link [Str "http://docs.python.org/library/functions.html#range"] ("http://docs.python.org/library/functions.html#range","")]]]] ,Para [Str "URL",Space,Str "note.",Note [Plain [Link ("",[],[]) [Str "http://docs.python.org/library/functions.html#range"] ("http://docs.python.org/library/functions.html#range","")]]]]

View file

@ -171,6 +171,10 @@ http://pandoc.org
[[File:example.jpg|frameless|border|30x40px|caption]] [[File:example.jpg|frameless|border|30x40px|caption]]
[[File:example.jpg|frameless|border|30px|caption]]
[[File:example.jpg|page=4|30px|border|caption]]
[[File:example.jpg]] [[File:example.jpg]]
[[Archivo:example_es.jpg]] [[Archivo:example_es.jpg]]

View file

@ -1 +1 @@
[Header 1 ("a-chapter",[],[]) [Span ("anchor",[],[]) [],Str "A",Space,Str "chapter"],Para [Str "Some",Space,Str "text."],Header 1 ("another-chapter",[],[]) [Str "Another",Space,Str "chapter"],Para [Str "A",Space,Str "reference",Space,Str "to",Space,Str "."],Para [Str "A",Space,Str "reference",Space,Str "to",Space,Link [Str "A",Space,Str "chapter"] ("#anchor",""),Str "."]] [Header 1 ("a-chapter",[],[]) [Span ("anchor",[],[]) [],Str "A",Space,Str "chapter"],Para [Str "Some",Space,Str "text."],Header 1 ("another-chapter",[],[]) [Str "Another",Space,Str "chapter"],Para [Str "A",Space,Str "reference",Space,Str "to",Space,Str "."],Para [Str "A",Space,Str "reference",Space,Str "to",Space,Link ("",[],[]) [Str "A",Space,Str "chapter"] ("#anchor",""),Str "."]]

View file

@ -1 +1 @@
[OrderedList (1,Decimal,Period) [[Plain [Span ("anchor",[],[]) [],Str "A",Space,Str "list",Space,Str "item"]],[Plain [Str "Another",Space,Str "list",Space,Str "item"]]],Para [Str "A",Space,Str "reference",Space,Str "to",Space,Str "list",Space,Str "item",Space,Link [Str "1."] ("#anchor",""),Str "."],Para [],Para []] [OrderedList (1,Decimal,Period) [[Plain [Span ("anchor",[],[]) [],Str "A",Space,Str "list",Space,Str "item"]],[Plain [Str "Another",Space,Str "list",Space,Str "item"]]],Para [Str "A",Space,Str "reference",Space,Str "to",Space,Str "list",Space,Str "item",Space,Link ("",[],[]) [Str "1."] ("#anchor",""),Str "."],Para [],Para []]

View file

@ -1 +1 @@
[Para [Span ("an anchor",[],[]) [],Str "Some",Space,Str "text."],Para [Str "A",Space,Str "reference",Space,Str "to",Space,Link [Str "Some",Space,Str "text"] ("#an anchor",""),Str "."]] [Para [Span ("an anchor",[],[]) [],Str "Some",Space,Str "text."],Para [Str "A",Space,Str "reference",Space,Str "to",Space,Link ("",[],[]) [Str "Some",Space,Str "text"] ("#an anchor",""),Str "."]]

View file

@ -7,7 +7,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Dave",Spa
,Header 3 ("",[],[]) [Strong [Str "Nevada"]] ,Header 3 ("",[],[]) [Strong [Str "Nevada"]]
,Para [Str "I",Space,Str "lived",Space,Str "here",Space,Emph [Str "once"],Str "."] ,Para [Str "I",Space,Str "lived",Space,Str "here",Space,Emph [Str "once"],Str "."]
,Para [Str "Loved",Space,Str "it."] ,Para [Str "Loved",Space,Str "it."]
,Header 4 ("",[],[]) [Link [Str "Reno"] ("http://www.reno.gov","")] ,Header 4 ("",[],[]) [Link ("",[],[]) [Str "Reno"] ("http://www.reno.gov","")]
,Header 4 ("",[],[]) [Str "Las",Space,Str "Vegas"] ,Header 4 ("",[],[]) [Str "Las",Space,Str "Vegas"]
,Header 4 ("",[],[]) [Str "Ely"] ,Header 4 ("",[],[]) [Str "Ely"]
,Header 4 ("",[],[]) [Str "Gerlach"] ,Header 4 ("",[],[]) [Str "Gerlach"]

View file

@ -210,20 +210,20 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Str "Plus:",Space,Str "+"] ,Para [Str "Plus:",Space,Str "+"]
,Para [Str "Minus:",Space,Str "-"] ,Para [Str "Minus:",Space,Str "-"]
,Header 1 ("links",[],[]) [Str "Links"] ,Header 1 ("links",[],[]) [Str "Links"]
,Para [Str "Explicit:",Space,Str "a",Space,Link [Str "URL"] ("/url/",""),Str "."] ,Para [Str "Explicit:",Space,Str "a",Space,Link ("",[],[]) [Str "URL"] ("/url/",""),Str "."]
,Para [Str "Two",Space,Str "anonymous",Space,Str "links:",Space,Link [Str "the",Space,Str "first"] ("/url1/",""),Space,Str "and",Space,Link [Str "the",Space,Str "second"] ("/url2/","")] ,Para [Str "Two",Space,Str "anonymous",Space,Str "links:",Space,Link ("",[],[]) [Str "the",Space,Str "first"] ("/url1/",""),Space,Str "and",Space,Link ("",[],[]) [Str "the",Space,Str "second"] ("/url2/","")]
,Para [Str "Reference",Space,Str "links:",Space,Link [Str "link1"] ("/url1/",""),Space,Str "and",Space,Link [Str "link2"] ("/url2/",""),Space,Str "and",Space,Link [Str "link1"] ("/url1/",""),Space,Str "again."] ,Para [Str "Reference",Space,Str "links:",Space,Link ("",[],[]) [Str "link1"] ("/url1/",""),Space,Str "and",Space,Link ("",[],[]) [Str "link2"] ("/url2/",""),Space,Str "and",Space,Link ("",[],[]) [Str "link1"] ("/url1/",""),Space,Str "again."]
,Para [Str "Here\8217s",Space,Str "a",Space,Link [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "a",Space,Link ("",[],[]) [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link [Str "AT&T"] ("/url/",""),Str "."] ,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link ("",[],[]) [Str "AT&T"] ("/url/",""),Str "."]
,Para [Str "Autolinks:",Space,Link [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2",""),Space,Str "and",Space,Link [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net",""),Str "."] ,Para [Str "Autolinks:",Space,Link ("",[],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2",""),Space,Str "and",Space,Link ("",[],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net",""),Str "."]
,Para [Str "But",Space,Str "not",Space,Str "here:"] ,Para [Str "But",Space,Str "not",Space,Str "here:"]
,CodeBlock ("",[],[]) "http://example.com/" ,CodeBlock ("",[],[]) "http://example.com/"
,Header 1 ("images",[],[]) [Str "Images"] ,Header 1 ("images",[],[]) [Str "Images"]
,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"] ,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
,Para [Image [Str "image"] ("lalune.jpg","")] ,Para [Image ("",[],[]) [Str "image"] ("lalune.jpg","")]
,Para [Image [Str "Voyage dans la Lune"] ("lalune.jpg","")] ,Para [Image ("",[],[]) [Str "Voyage dans la Lune"] ("lalune.jpg","")]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon."] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [Str "movie"] ("movie.jpg",""),Space,Str "icon."]
,Para [Str "And",Space,Str "an",Space,Link [Image [Str "A movie"] ("movie.jpg","")] ("/url",""),Str "."] ,Para [Str "And",Space,Str "an",Space,Link ("",[],[]) [Image ("",[],[]) [Str "A movie"] ("movie.jpg","")] ("/url",""),Str "."]
,Header 1 ("comments",[],[]) [Str "Comments"] ,Header 1 ("comments",[],[]) [Str "Comments"]
,Para [Str "First",Space,Str "paragraph"] ,Para [Str "First",Space,Str "paragraph"]
,Para [Str "Another",Space,Str "paragraph"] ,Para [Str "Another",Space,Str "paragraph"]

View file

@ -2,7 +2,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."] [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,HorizontalRule ,HorizontalRule
,Header 1 ("headers",[],[]) [Str "Headers"] ,Header 1 ("headers",[],[]) [Str "Headers"]
,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embedded",Space,Str "link"] ("/url","")] ,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link ("",[],[]) [Str "embedded",Space,Str "link"] ("/url","")]
,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]] ,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]]
,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"] ,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"]
,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"] ,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"]
@ -286,7 +286,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"] ,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"]
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."] ,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."]
,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."] ,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."]
,Para [Str "An",Space,Emph [Link [Str "emphasized",Space,Str "link"] ("/url","")],Str "."] ,Para [Str "An",Space,Emph [Link ("",[],[]) [Str "emphasized",Space,Str "link"] ("/url","")],Str "."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]] ,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."] ,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]] ,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
@ -302,7 +302,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters."] ,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters."]
,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]] ,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]]
,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70\8217s?"] ,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70\8217s?"]
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."] ,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link ("",[],[]) [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."]
,Para [Str "Some",Space,Str "dashes:",Space,Str "one\8212two",Space,Str "\8212",Space,Str "three\8212four",Space,Str "\8212",Space,Str "five."] ,Para [Str "Some",Space,Str "dashes:",Space,Str "one\8212two",Space,Str "\8212",Space,Str "three\8212four",Space,Str "\8212",Space,Str "five."]
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5\8211\&7,",Space,Str "255\8211\&66,",Space,Str "1987\8211\&1999."] ,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5\8211\&7,",Space,Str "255\8211\&66,",Space,Str "1987\8211\&1999."]
,Para [Str "Ellipses\8230and\8230and\8230."] ,Para [Str "Ellipses\8230and\8230and\8230."]
@ -358,52 +358,52 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,HorizontalRule ,HorizontalRule
,Header 1 ("links",[],[]) [Str "Links"] ,Header 1 ("links",[],[]) [Str "Links"]
,Header 2 ("explicit",[],[]) [Str "Explicit"] ,Header 2 ("explicit",[],[]) [Str "Explicit"]
,Para [Str "Just",Space,Str "a",Space,Link [Str "URL"] ("/url/",""),Str "."] ,Para [Str "Just",Space,Str "a",Space,Link ("",[],[]) [Str "URL"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title"),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title"),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by two spaces"),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by two spaces"),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by a tab"),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by a tab"),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with \"quotes\" in it")] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with \"quotes\" in it")]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with single quotes")] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with single quotes")]
,Para [Link [Str "with_underscore"] ("/url/with_underscore","")] ,Para [Link ("",[],[]) [Str "with_underscore"] ("/url/with_underscore","")]
,Para [Link [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")] ,Para [Link ("",[],[]) [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")]
,Para [Link [Str "Empty"] ("",""),Str "."] ,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."]
,Header 2 ("reference",[],[]) [Str "Reference"] ,Header 2 ("reference",[],[]) [Str "Reference"]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "With",Space,Link [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."] ,Para [Str "With",Space,Link ("",[],[]) [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."]
,Para [Link [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."] ,Para [Link ("",[],[]) [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."]
,Para [Str "Indented",Space,Link [Str "once"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "once"] ("/url",""),Str "."]
,Para [Str "Indented",Space,Link [Str "twice"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "twice"] ("/url",""),Str "."]
,Para [Str "Indented",Space,Link [Str "thrice"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "thrice"] ("/url",""),Str "."]
,Para [Str "This",Space,Str "should",Space,Str "[not][]",Space,Str "be",Space,Str "a",Space,Str "link."] ,Para [Str "This",Space,Str "should",Space,Str "[not][]",Space,Str "be",Space,Str "a",Space,Str "link."]
,CodeBlock ("",[],[]) "[not]: /url" ,CodeBlock ("",[],[]) "[not]: /url"
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/","Title with \"quotes\" inside"),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/","Title with \"quotes\" inside"),Str "."]
,Para [Str "Foo",Space,Link [Str "biz"] ("/url/","Title with \"quote\" inside"),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "biz"] ("/url/","Title with \"quote\" inside"),Str "."]
,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"] ,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"]
,Para [Str "Here\8217s",Space,Str "a",Space,Link [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "a",Space,Link ("",[],[]) [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link [Str "AT&T"] ("http://att.com/","AT&T"),Str "."] ,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link ("",[],[]) [Str "AT&T"] ("http://att.com/","AT&T"),Str "."]
,Para [Str "Here\8217s",Space,Str "an",Space,Link [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
,Para [Str "Here\8217s",Space,Str "an",Space,Link [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."]
,Header 2 ("autolinks",[],[]) [Str "Autolinks"] ,Header 2 ("autolinks",[],[]) [Str "Autolinks"]
,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")] ,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link ("",[],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
,BulletList ,BulletList
[[Plain [Str "In",Space,Str "a",Space,Str "list?"]] [[Plain [Str "In",Space,Str "a",Space,Str "list?"]]
,[Plain [Link [Str "http://example.com/"] ("http://example.com/","")]] ,[Plain [Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
,[Plain [Str "It",Space,Str "should."]]] ,[Plain [Str "It",Space,Str "should."]]]
,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")] ,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",[],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
,BlockQuote ,BlockQuote
[Para [Str "Blockquoted:",Space,Link [Str "http://example.com/"] ("http://example.com/","")]] [Para [Str "Blockquoted:",Space,Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"] ,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"]
,CodeBlock ("",[],[]) "or here: <http://example.com/>" ,CodeBlock ("",[],[]) "or here: <http://example.com/>"
,HorizontalRule ,HorizontalRule
,Header 1 ("images",[],[]) [Str "Images"] ,Header 1 ("images",[],[]) [Str "Images"]
,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"] ,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
,Para [Image [Str "lalune"] ("lalune.jpg","fig:Voyage dans la Lune")] ,Para [Image ("",[],[]) [Str "lalune"] ("lalune.jpg","fig:Voyage dans la Lune")]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon."] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [Str "movie"] ("movie.jpg",""),Space,Str "icon."]
,HorizontalRule ,HorizontalRule
,Header 1 ("footnotes",[],[]) [Str "Footnotes"] ,Header 1 ("footnotes",[],[]) [Str "Footnotes"]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link ("",[],[]) [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]]
,BlockQuote ,BlockQuote
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]] [Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]]
,OrderedList (1,Decimal,Period) ,OrderedList (1,Decimal,Period)

View file

@ -2,7 +2,7 @@ Pandoc (Meta {unMeta = fromList []})
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc",Space,Str "Textile",Space,Str "Reader.",Space,Str "Part",Space,Str "of",Space,Str "it",Space,Str "comes",LineBreak,Str "from",Space,Str "John",Space,Str "Gruber's",Space,Str "markdown",Space,Str "test",Space,Str "suite."] [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc",Space,Str "Textile",Space,Str "Reader.",Space,Str "Part",Space,Str "of",Space,Str "it",Space,Str "comes",LineBreak,Str "from",Space,Str "John",Space,Str "Gruber's",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,HorizontalRule ,HorizontalRule
,Header 1 ("headers",[],[]) [Str "Headers"] ,Header 1 ("headers",[],[]) [Str "Headers"]
,Header 2 ("level-2-with-an-embeded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embeded",Space,Str "link"] ("http://www.example.com","")] ,Header 2 ("level-2-with-an-embeded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link ("",[],[]) [Str "embeded",Space,Str "link"] ("http://www.example.com","")]
,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Strong [Str "emphasis"]] ,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Strong [Str "emphasis"]]
,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"] ,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"]
,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"] ,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"]
@ -84,7 +84,7 @@ Pandoc (Meta {unMeta = fromList []})
,([Str "beer"], ,([Str "beer"],
[[Plain [Str "fresh",Space,Str "and",Space,Str "bitter"]]])] [[Plain [Str "fresh",Space,Str "and",Space,Str "bitter"]]])]
,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"] ,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"]
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str ".",LineBreak,Str "Hyphenated-words-are-ok,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "strange_underscore_notation.",LineBreak,Str "A",Space,Link [Strong [Str "strong",Space,Str "link"]] ("http://www.foobar.com",""),Str "."] ,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str ".",LineBreak,Str "Hyphenated-words-are-ok,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "strange_underscore_notation.",LineBreak,Str "A",Space,Link ("",[],[]) [Strong [Str "strong",Space,Str "link"]] ("http://www.foobar.com",""),Str "."]
,Para [Emph [Strong [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]],LineBreak,Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Space,Str "and",Space,Emph [Strong [Str "that",Space,Str "one"]],Str ".",LineBreak,Strikeout [Str "This",Space,Str "is",Space,Str "strikeout",Space,Str "and",Space,Strong [Str "strong"]]] ,Para [Emph [Strong [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]],LineBreak,Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Space,Str "and",Space,Emph [Strong [Str "that",Space,Str "one"]],Str ".",LineBreak,Strikeout [Str "This",Space,Str "is",Space,Str "strikeout",Space,Str "and",Space,Strong [Str "strong"]]]
,Para [Str "Superscripts:",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Space,Superscript [Strong [Str "hello"]],Space,Str "a",Superscript [Str "hello",Space,Str "there"],Str ".",LineBreak,Str "Subscripts:",Space,Subscript [Str "here"],Space,Str "H",Space,Subscript [Str "2"],Str "O,",Space,Str "H",Space,Subscript [Str "23"],Str "O,",Space,Str "H",Space,Subscript [Str "many",Space,Str "of",Space,Str "them"],Str "O."] ,Para [Str "Superscripts:",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Space,Superscript [Strong [Str "hello"]],Space,Str "a",Superscript [Str "hello",Space,Str "there"],Str ".",LineBreak,Str "Subscripts:",Space,Subscript [Str "here"],Space,Str "H",Space,Subscript [Str "2"],Str "O,",Space,Str "H",Space,Subscript [Str "23"],Str "O,",Space,Str "H",Space,Subscript [Str "many",Space,Str "of",Space,Str "them"],Str "O."]
,Para [Str "Dashes",Space,Str ":",Space,Str "How",Space,Str "cool",Space,Str "--",Space,Str "automatic",Space,Str "dashes."] ,Para [Str "Dashes",Space,Str ":",Space,Str "How",Space,Str "cool",Space,Str "--",Space,Str "automatic",Space,Str "dashes."]
@ -92,11 +92,11 @@ Pandoc (Meta {unMeta = fromList []})
,Para [Str "Quotes",Space,Str "and",Space,Str "apostrophes",Space,Str ":",Space,Str "\"I'd",Space,Str "like",Space,Str "to",Space,Str "thank",Space,Str "you\"",Space,Str "for",Space,Str "example."] ,Para [Str "Quotes",Space,Str "and",Space,Str "apostrophes",Space,Str ":",Space,Str "\"I'd",Space,Str "like",Space,Str "to",Space,Str "thank",Space,Str "you\"",Space,Str "for",Space,Str "example."]
,Header 1 ("links",[],[]) [Str "Links"] ,Header 1 ("links",[],[]) [Str "Links"]
,Header 2 ("explicit",[],[]) [Str "Explicit"] ,Header 2 ("explicit",[],[]) [Str "Explicit"]
,Para [Str "Just",Space,Str "a",Space,Link [Str "url"] ("http://www.url.com","")] ,Para [Str "Just",Space,Str "a",Space,Link ("",[],[]) [Str "url"] ("http://www.url.com","")]
,Para [Link [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")] ,Para [Link ("",[],[]) [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")]
,Para [Str "Automatic",Space,Str "linking",Space,Str "to",Space,Link [Str "http://www.example.com"] ("http://www.example.com",""),Str "."] ,Para [Str "Automatic",Space,Str "linking",Space,Str "to",Space,Link ("",[],[]) [Str "http://www.example.com"] ("http://www.example.com",""),Str "."]
,Para [Link [Str "Example"] ("http://www.example.com/",""),Str ":",Space,Str "Example",Space,Str "of",Space,Str "a",Space,Str "link",Space,Str "followed",Space,Str "by",Space,Str "a",Space,Str "colon."] ,Para [Link ("",[],[]) [Str "Example"] ("http://www.example.com/",""),Str ":",Space,Str "Example",Space,Str "of",Space,Str "a",Space,Str "link",Space,Str "followed",Space,Str "by",Space,Str "a",Space,Str "colon."]
,Para [Str "A",Space,Str "link",Link [Str "with",Space,Str "brackets"] ("http://www.example.com",""),Str "and",Space,Str "no",Space,Str "spaces."] ,Para [Str "A",Space,Str "link",Link ("",[],[]) [Str "with",Space,Str "brackets"] ("http://www.example.com",""),Str "and",Space,Str "no",Space,Str "spaces."]
,Header 1 ("tables",[],[]) [Str "Tables"] ,Header 1 ("tables",[],[]) [Str "Tables"]
,Para [Str "Textile",Space,Str "allows",Space,Str "tables",Space,Str "with",Space,Str "and",Space,Str "without",Space,Str "headers",Space,Str ":"] ,Para [Str "Textile",Space,Str "allows",Space,Str "tables",Space,Str "with",Space,Str "and",Space,Str "without",Space,Str "headers",Space,Str ":"]
,Header 2 ("without-headers",[],[]) [Str "Without",Space,Str "headers"] ,Header 2 ("without-headers",[],[]) [Str "Without",Space,Str "headers"]
@ -130,7 +130,7 @@ Pandoc (Meta {unMeta = fromList []})
,[Plain [Str "45"]] ,[Plain [Str "45"]]
,[Plain [Str "f"]]]] ,[Plain [Str "f"]]]]
,Header 1 ("images",[],[]) [Str "Images"] ,Header 1 ("images",[],[]) [Str "Images"]
,Para [Str "Textile",Space,Str "inline",Space,Str "image",Space,Str "syntax,",Space,Str "like",LineBreak,Str "here",Space,Image [Str "this is the alt text"] ("this_is_an_image.png","this is the alt text"),LineBreak,Str "and",Space,Str "here",Space,Image [Str ""] ("this_is_an_image.png",""),Str "."] ,Para [Str "Textile",Space,Str "inline",Space,Str "image",Space,Str "syntax,",Space,Str "like",LineBreak,Str "here",Space,Image ("",[],[]) [Str "this is the alt text"] ("this_is_an_image.png","this is the alt text"),LineBreak,Str "and",Space,Str "here",Space,Image ("",[],[]) [Str ""] ("this_is_an_image.png",""),Str "."]
,Header 1 ("attributes",[],[]) [Str "Attributes"] ,Header 1 ("attributes",[],[]) [Str "Attributes"]
,Header 2 ("ident",["bar","foo"],[("style","color:red"),("lang","en")]) [Str "HTML",Space,Str "and",Space,Str "CSS",Space,Str "attributes",Space,Str "are",Space,Str "parsed",Space,Str "in",Space,Str "headers."] ,Header 2 ("ident",["bar","foo"],[("style","color:red"),("lang","en")]) [Str "HTML",Space,Str "and",Space,Str "CSS",Space,Str "attributes",Space,Str "are",Space,Str "parsed",Space,Str "in",Space,Str "headers."]
,Para [Str "as",Space,Str "well",Space,Str "as",Space,Strong [Span ("",["foo"],[]) [Str "inline",Space,Str "attributes"]],Space,Str "of",Space,Span ("",[],[("style","color:red")]) [Str "all",Space,Str "kind"]] ,Para [Str "as",Space,Str "well",Space,Str "as",Space,Strong [Span ("",["foo"],[]) [Str "inline",Space,Str "attributes"]],Space,Str "of",Space,Span ("",[],[("style","color:red")]) [Str "all",Space,Str "kind"]]

View file

@ -43,10 +43,10 @@ Pandoc (Meta {unMeta = fromList []})
,Para [Str "With",Space,Str "two",Space,Str "paragraphs."]] ,Para [Str "With",Space,Str "two",Space,Str "paragraphs."]]
,Para [Str "Nother",Space,Str "paragraph."] ,Para [Str "Nother",Space,Str "paragraph."]
,Header 1 ("external-links",[],[]) [Str "external",Space,Str "links"] ,Header 1 ("external-links",[],[]) [Str "external",Space,Str "links"]
,Para [Link [Emph [Str "Google"],Space,Str "search",Space,Str "engine"] ("http://google.com","")] ,Para [Link ("",[],[]) [Emph [Str "Google"],Space,Str "search",Space,Str "engine"] ("http://google.com","")]
,Para [Link [Str "http://pandoc.org"] ("http://pandoc.org","")] ,Para [Link ("",[],[]) [Str "http://pandoc.org"] ("http://pandoc.org","")]
,Para [Link [Str "http://google.com"] ("http://google.com",""),Space,Link [Str "http://yahoo.com"] ("http://yahoo.com","")] ,Para [Link ("",[],[]) [Str "http://google.com"] ("http://google.com",""),Space,Link ("",[],[]) [Str "http://yahoo.com"] ("http://yahoo.com","")]
,Para [Link [Str "email",Space,Str "me"] ("mailto:info@example.org","")] ,Para [Link ("",[],[]) [Str "email",Space,Str "me"] ("mailto:info@example.org","")]
,Para [Str "http://google.com"] ,Para [Str "http://google.com"]
,Para [Str "http://google.com"] ,Para [Str "http://google.com"]
,Para [Str "http://google.com"] ,Para [Str "http://google.com"]

File diff suppressed because one or more lines are too long

View file

@ -2544,27 +2544,26 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
</ParagraphStyleRange> </ParagraphStyleRange>
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph"> <ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle"> <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Rectangle Self="uec" ItemTransform="1 0 0 1 75 -50"> <Rectangle Self="uec" StrokeWeight="0" ItemTransform="1.00000 0 0 1.00000 75.00000 -75.00000">
<Properties> <Properties>
<PathGeometry> <PathGeometry>
<GeometryPathType PathOpen="false"> <GeometryPathType PathOpen="false">
<PathPointArray> <PathPointArray>
<PathPointType Anchor="-75 -50" LeftDirection="-75 -50" RightDirection="-75 -50" /> <PathPointType Anchor="-75.00000 -75.00000" LeftDirection="-75.00000 -75.00000" RightDirection="-75.00000 -75.00000" />
<PathPointType Anchor="-75 50" LeftDirection="-75 50" RightDirection="-75 50" /> <PathPointType Anchor="-75.00000 75.00000" LeftDirection="-75.00000 75.00000" RightDirection="-75.00000 75.00000" />
<PathPointType Anchor="75 50" LeftDirection="75 50" RightDirection="75 50" /> <PathPointType Anchor="75.00000 75.00000" LeftDirection="75.00000 75.00000" RightDirection="75.00000 75.00000" />
<PathPointType Anchor="75 -50" LeftDirection="75 -50" RightDirection="75 -50" /> <PathPointType Anchor="75.00000 -75.00000" LeftDirection="75.00000 -75.00000" RightDirection="75.00000 -75.00000" />
</PathPointArray> </PathPointArray>
</GeometryPathType> </GeometryPathType>
</PathGeometry> </PathGeometry>
</Properties> </Properties>
<Image Self="ue6" ItemTransform="1.0 0 0 1.0 -75 -50"> <Image Self="ue6" ItemTransform="1.00000 0 0 1.00000 -75.00000 -75.00000">
<Properties> <Properties>
<Profile type="string"> <Profile type="string">
$ID/Embedded $ID/Embedded
<GraphicBounds Left="0" Top="0" Right="150" Bottom="100" />
</Profile> </Profile>
</Properties> </Properties>
<Link Self="ueb" LinkResourceURI="file:lalune.jpg" /> <Link Self="ueb" LinkResourceURI="file://./lalune.jpg" />
</Image> </Image>
</Rectangle> </Rectangle>
</CharacterStyleRange><Br /> </CharacterStyleRange><Br />
@ -2574,27 +2573,26 @@ These should not be escaped: \$ \\ \&gt; \[ \{</Content>
<Content>Here is a movie </Content> <Content>Here is a movie </Content>
</CharacterStyleRange> </CharacterStyleRange>
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle"> <CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
<Rectangle Self="uec" ItemTransform="1 0 0 1 75 -50"> <Rectangle Self="uec" StrokeWeight="0" ItemTransform="1.00000 0 0 1.00000 10.00000 -11.00000">
<Properties> <Properties>
<PathGeometry> <PathGeometry>
<GeometryPathType PathOpen="false"> <GeometryPathType PathOpen="false">
<PathPointArray> <PathPointArray>
<PathPointType Anchor="-75 -50" LeftDirection="-75 -50" RightDirection="-75 -50" /> <PathPointType Anchor="-10.00000 -11.00000" LeftDirection="-10.00000 -11.00000" RightDirection="-10.00000 -11.00000" />
<PathPointType Anchor="-75 50" LeftDirection="-75 50" RightDirection="-75 50" /> <PathPointType Anchor="-10.00000 11.00000" LeftDirection="-10.00000 11.00000" RightDirection="-10.00000 11.00000" />
<PathPointType Anchor="75 50" LeftDirection="75 50" RightDirection="75 50" /> <PathPointType Anchor="10.00000 11.00000" LeftDirection="10.00000 11.00000" RightDirection="10.00000 11.00000" />
<PathPointType Anchor="75 -50" LeftDirection="75 -50" RightDirection="75 -50" /> <PathPointType Anchor="10.00000 -11.00000" LeftDirection="10.00000 -11.00000" RightDirection="10.00000 -11.00000" />
</PathPointArray> </PathPointArray>
</GeometryPathType> </GeometryPathType>
</PathGeometry> </PathGeometry>
</Properties> </Properties>
<Image Self="ue6" ItemTransform="1.0 0 0 1.0 -75 -50"> <Image Self="ue6" ItemTransform="1.00000 0 0 1.00000 -10.00000 -11.00000">
<Properties> <Properties>
<Profile type="string"> <Profile type="string">
$ID/Embedded $ID/Embedded
<GraphicBounds Left="0" Top="0" Right="150" Bottom="100" />
</Profile> </Profile>
</Properties> </Properties>
<Link Self="ueb" LinkResourceURI="file:movie.jpg" /> <Link Self="ueb" LinkResourceURI="file://./movie.jpg" />
</Image> </Image>
</Rectangle> </Rectangle>
</CharacterStyleRange> </CharacterStyleRange>

View file

@ -2,7 +2,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."] [Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
,HorizontalRule ,HorizontalRule
,Header 1 ("headers",[],[]) [Str "Headers"] ,Header 1 ("headers",[],[]) [Str "Headers"]
,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embedded",Space,Str "link"] ("/url","")] ,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link ("",[],[]) [Str "embedded",Space,Str "link"] ("/url","")]
,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]] ,Header 3 ("level-3-with-emphasis",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]]
,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"] ,Header 4 ("level-4",[],[]) [Str "Level",Space,Str "4"]
,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"] ,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"]
@ -286,7 +286,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"] ,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"]
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."] ,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str "."]
,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."] ,Para [Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str "."]
,Para [Str "An",Space,Emph [Link [Str "emphasized",Space,Str "link"] ("/url","")],Str "."] ,Para [Str "An",Space,Emph [Link ("",[],[]) [Str "emphasized",Space,Str "link"] ("/url","")],Str "."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]] ,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."] ,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]] ,Para [Strong [Emph [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]]]
@ -302,7 +302,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters."] ,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters."]
,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]] ,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]]
,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70\8217s?"] ,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70\8217s?"]
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."] ,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link ("",[],[]) [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."]
,Para [Str "Some",Space,Str "dashes:",Space,Str "one\8212two",Space,Str "\8212",Space,Str "three\8212four",Space,Str "\8212",Space,Str "five."] ,Para [Str "Some",Space,Str "dashes:",Space,Str "one\8212two",Space,Str "\8212",Space,Str "three\8212four",Space,Str "\8212",Space,Str "five."]
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5\8211\&7,",Space,Str "255\8211\&66,",Space,Str "1987\8211\&1999."] ,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5\8211\&7,",Space,Str "255\8211\&66,",Space,Str "1987\8211\&1999."]
,Para [Str "Ellipses\8230and\8230and\8230."] ,Para [Str "Ellipses\8230and\8230and\8230."]
@ -358,52 +358,52 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
,HorizontalRule ,HorizontalRule
,Header 1 ("links",[],[]) [Str "Links"] ,Header 1 ("links",[],[]) [Str "Links"]
,Header 2 ("explicit",[],[]) [Str "Explicit"] ,Header 2 ("explicit",[],[]) [Str "Explicit"]
,Para [Str "Just",Space,Str "a",Space,Link [Str "URL"] ("/url/",""),Str "."] ,Para [Str "Just",Space,Str "a",Space,Link ("",[],[]) [Str "URL"] ("/url/",""),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title"),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title"),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by two spaces"),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by two spaces"),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by a tab"),Str "."] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title preceded by a tab"),Str "."]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with \"quotes\" in it")] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with \"quotes\" in it")]
,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with single quotes")] ,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with single quotes")]
,Para [Link [Str "with_underscore"] ("/url/with_underscore","")] ,Para [Link ("",[],[]) [Str "with_underscore"] ("/url/with_underscore","")]
,Para [Link [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")] ,Para [Link ("",[],[]) [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")]
,Para [Link [Str "Empty"] ("",""),Str "."] ,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."]
,Header 2 ("reference",[],[]) [Str "Reference"] ,Header 2 ("reference",[],[]) [Str "Reference"]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."]
,Para [Str "With",Space,Link [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."] ,Para [Str "With",Space,Link ("",[],[]) [Str "embedded",Space,Str "[brackets]"] ("/url/",""),Str "."]
,Para [Link [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."] ,Para [Link ("",[],[]) [Str "b"] ("/url/",""),Space,Str "by",Space,Str "itself",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "link."]
,Para [Str "Indented",Space,Link [Str "once"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "once"] ("/url",""),Str "."]
,Para [Str "Indented",Space,Link [Str "twice"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "twice"] ("/url",""),Str "."]
,Para [Str "Indented",Space,Link [Str "thrice"] ("/url",""),Str "."] ,Para [Str "Indented",Space,Link ("",[],[]) [Str "thrice"] ("/url",""),Str "."]
,Para [Str "This",Space,Str "should",Space,Str "[not][]",Space,Str "be",Space,Str "a",Space,Str "link."] ,Para [Str "This",Space,Str "should",Space,Str "[not][]",Space,Str "be",Space,Str "a",Space,Str "link."]
,CodeBlock ("",[],[]) "[not]: /url" ,CodeBlock ("",[],[]) "[not]: /url"
,Para [Str "Foo",Space,Link [Str "bar"] ("/url/","Title with \"quotes\" inside"),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/","Title with \"quotes\" inside"),Str "."]
,Para [Str "Foo",Space,Link [Str "biz"] ("/url/","Title with \"quote\" inside"),Str "."] ,Para [Str "Foo",Space,Link ("",[],[]) [Str "biz"] ("/url/","Title with \"quote\" inside"),Str "."]
,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"] ,Header 2 ("with-ampersands",[],[]) [Str "With",Space,Str "ampersands"]
,Para [Str "Here\8217s",Space,Str "a",Space,Link [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "a",Space,Link ("",[],[]) [Str "link",Space,Str "with",Space,Str "an",Space,Str "ampersand",Space,Str "in",Space,Str "the",Space,Str "URL"] ("http://example.com/?foo=1&bar=2",""),Str "."]
,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link [Str "AT&T"] ("http://att.com/","AT&T"),Str "."] ,Para [Str "Here\8217s",Space,Str "a",Space,Str "link",Space,Str "with",Space,Str "an",Space,Str "amersand",Space,Str "in",Space,Str "the",Space,Str "link",Space,Str "text:",Space,Link ("",[],[]) [Str "AT&T"] ("http://att.com/","AT&T"),Str "."]
,Para [Str "Here\8217s",Space,Str "an",Space,Link [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link"] ("/script?foo=1&bar=2",""),Str "."]
,Para [Str "Here\8217s",Space,Str "an",Space,Link [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."] ,Para [Str "Here\8217s",Space,Str "an",Space,Link ("",[],[]) [Str "inline",Space,Str "link",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?foo=1&bar=2",""),Str "."]
,Header 2 ("autolinks",[],[]) [Str "Autolinks"] ,Header 2 ("autolinks",[],[]) [Str "Autolinks"]
,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")] ,Para [Str "With",Space,Str "an",Space,Str "ampersand:",Space,Link ("",[],[]) [Str "http://example.com/?foo=1&bar=2"] ("http://example.com/?foo=1&bar=2","")]
,BulletList ,BulletList
[[Plain [Str "In",Space,Str "a",Space,Str "list?"]] [[Plain [Str "In",Space,Str "a",Space,Str "list?"]]
,[Plain [Link [Str "http://example.com/"] ("http://example.com/","")]] ,[Plain [Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
,[Plain [Str "It",Space,Str "should."]]] ,[Plain [Str "It",Space,Str "should."]]]
,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")] ,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Link ("",[],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")]
,BlockQuote ,BlockQuote
[Para [Str "Blockquoted:",Space,Link [Str "http://example.com/"] ("http://example.com/","")]] [Para [Str "Blockquoted:",Space,Link ("",[],[]) [Str "http://example.com/"] ("http://example.com/","")]]
,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"] ,Para [Str "Auto-links",Space,Str "should",Space,Str "not",Space,Str "occur",Space,Str "here:",Space,Code ("",[],[]) "<http://example.com/>"]
,CodeBlock ("",[],[]) "or here: <http://example.com/>" ,CodeBlock ("",[],[]) "or here: <http://example.com/>"
,HorizontalRule ,HorizontalRule
,Header 1 ("images",[],[]) [Str "Images"] ,Header 1 ("images",[],[]) [Str "Images"]
,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"] ,Para [Str "From",Space,Quoted DoubleQuote [Str "Voyage",Space,Str "dans",Space,Str "la",Space,Str "Lune"],Space,Str "by",Space,Str "Georges",Space,Str "Melies",Space,Str "(1902):"]
,Para [Image [Str "lalune"] ("lalune.jpg","fig:Voyage dans la Lune")] ,Para [Image ("",[],[]) [Str "lalune"] ("lalune.jpg","fig:Voyage dans la Lune")]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image [Str "movie"] ("movie.jpg",""),Space,Str "icon."] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [Str "movie"] ("movie.jpg",""),Space,Str "icon."]
,HorizontalRule ,HorizontalRule
,Header 1 ("footnotes",[],[]) [Str "Footnotes"] ,Header 1 ("footnotes",[],[]) [Str "Footnotes"]
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]] ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link ("",[],[]) [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]]
,BlockQuote ,BlockQuote
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]] [Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]]
,OrderedList (1,Decimal,Period) ,OrderedList (1,Decimal,Period)

File diff suppressed because one or more lines are too long