From 2e8064346d17bbb25a16650fc074393e834d67f7 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 2 Apr 2015 21:09:01 -0700 Subject: [PATCH 01/14] Pretty: comment fix (mb21). --- src/Text/Pandoc/Pretty.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs index 5e6450746..bb0091ca5 100644 --- a/src/Text/Pandoc/Pretty.hs +++ b/src/Text/Pandoc/Pretty.hs @@ -171,7 +171,7 @@ infixr 5 $$ else x <> cr <> y 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 ($+$) x y = if isEmpty x then y From 5df099957e0ed252a4d36161fc6c4ce7b18f528b Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 1 Apr 2015 15:52:32 -0700 Subject: [PATCH 02/14] Text.Pandoc.Options: modifications for image attributes. * Added `Ext_common_link_attributes` constructor to `Extension` (for link and image attributes). * Added this to `pandocExtensions` and `phpMarkdownExtraExtensions`. * Added `writerDpi` to `WriterOptions`. * pandoc.hs: Added `--dpi` option. * Updated README for `--dpi` and `common_link_attributes` extension. Patch due to mb21, with some modifications: `writerDpi` is now an `Int` rather than a `Double`. --- README | 72 +++++++++++++++++++++++++++++++++++--- pandoc.hs | 18 ++++++++-- src/Text/Pandoc/Options.hs | 5 +++ 3 files changed, 88 insertions(+), 7 deletions(-) diff --git a/README b/README index 3ecfaa813..3bb211341 100644 --- a/README +++ b/README @@ -420,14 +420,22 @@ General writer options : Print a system default data file. Files in the user data directory 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` : 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* : 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` @@ -2634,6 +2642,53 @@ nonbreaking space after the image: ![This image won't be a figure](/url/of/image.png)\ +#### Extension: `common_link_attributes` #### + +Attributes can be set on 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 + `` (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. + +Note that while attributes are also parsed on links, pandoc's internal +document model provides nowhere to put them, so they are presently +just ignored. + Footnotes --------- @@ -2908,9 +2963,15 @@ letters are omitted. #### Extension: `link_attributes` #### -Parses multimarkdown style key-value attributes on link and image references. -Note that pandoc's internal document model provides nowhere to put -these, so they are presently just ignored. +Parses multimarkdown style key-value attributes on link +and image references. (Since pandoc's internal document model +provides nowhere to put these for links, they are presently just +ignored, but they work for images.) + + 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` #### @@ -2953,7 +3014,8 @@ variants are supported: `markdown_phpextra` (PHP Markdown Extra) : `footnotes`, `pipe_tables`, `raw_html`, `markdown_attribute`, `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) : `pipe_tables`, `raw_html`, `tex_math_single_backslash`, diff --git a/pandoc.hs b/pandoc.hs index fb9b9abbf..e6488e99e 100644 --- a/pandoc.hs +++ b/pandoc.hs @@ -196,6 +196,7 @@ data Opt = Opt , optIgnoreArgs :: Bool -- ^ Ignore command-line arguments , optVerbose :: Bool -- ^ Verbose diagnostic output , optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst + , optDpi :: Int -- ^ Dpi , optWrapText :: Bool -- ^ Wrap text , optColumns :: Int -- ^ Line length in characters , optFilters :: [FilePath] -- ^ Filters to apply @@ -258,6 +259,7 @@ defaultOpts = Opt , optIgnoreArgs = False , optVerbose = False , optReferenceLinks = False + , optDpi = 96 , optWrapText = True , optColumns = 72 , optFilters = [] @@ -454,6 +456,16 @@ options = "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"] (NoArg (\opt -> return opt { optWrapText = False })) @@ -1012,8 +1024,8 @@ extractMedia media dir d = return $ walk (adjustImagePath dir fps) d adjustImagePath :: FilePath -> [FilePath] -> Inline -> Inline -adjustImagePath dir paths (Image lab (src, tit)) - | src `elem` paths = Image lab (dir ++ "/" ++ src, tit) +adjustImagePath dir paths (Image attr lab (src, tit)) + | src `elem` paths = Image attr lab (dir ++ "/" ++ src, tit) adjustImagePath _ _ x = x adjustMetadata :: M.Map String MetaValue -> Pandoc -> IO Pandoc @@ -1087,6 +1099,7 @@ main = do , optIgnoreArgs = ignoreArgs , optVerbose = verbose , optReferenceLinks = referenceLinks + , optDpi = dpi , optWrapText = wrap , optColumns = columns , optFilters = filters @@ -1304,6 +1317,7 @@ main = do writerNumberOffset = numberFrom, writerSectionDivs = sectionDivs, writerReferenceLinks = referenceLinks, + writerDpi = dpi, writerWrapText = wrap, writerColumns = columns, writerEmailObfuscation = obfuscationMethod, diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index 17eb4a15c..060fa6c05 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -86,6 +86,7 @@ data Extension = | Ext_markdown_attribute -- ^ Interpret text inside HTML as markdown -- iff container has attribute 'markdown' | 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_autolink_bare_uris -- ^ Make all absolute URIs into links | Ext_fancy_lists -- ^ Enable fancy list numbers and delimiters @@ -154,6 +155,7 @@ pandocExtensions = Set.fromList , Ext_subscript , Ext_auto_identifiers , Ext_header_attributes + , Ext_common_link_attributes , Ext_implicit_header_references , Ext_line_blocks , Ext_shortcut_reference_links @@ -187,6 +189,7 @@ phpMarkdownExtraExtensions = Set.fromList , Ext_definition_lists , Ext_intraword_underscores , Ext_header_attributes + , Ext_common_link_attributes , Ext_abbreviations , Ext_shortcut_reference_links ] @@ -324,6 +327,7 @@ data WriterOptions = WriterOptions , writerSectionDivs :: Bool -- ^ Put sections in div tags in HTML , writerExtensions :: Set Extension -- ^ Markdown extensions that can be used , 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 , writerColumns :: Int -- ^ Characters in a line (for text wrapping) , writerEmailObfuscation :: ObfuscationMethod -- ^ How to obfuscate emails @@ -370,6 +374,7 @@ instance Default WriterOptions where , writerSectionDivs = False , writerExtensions = pandocExtensions , writerReferenceLinks = False + , writerDpi = 96 , writerWrapText = True , writerColumns = 72 , writerEmailObfuscation = JavascriptObfuscation From b08330be8694f1feab97bb5207c1959c9fe9274f Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 1 Apr 2015 17:04:03 -0700 Subject: [PATCH 03/14] Require pandoc-types >= 1.14 --- pandoc.cabal | 6 +++--- 1 file changed, 3 insertions(+), 3 deletions(-) diff --git a/pandoc.cabal b/pandoc.cabal index d2bbff0c2..a2e7ee9bc 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -257,7 +257,7 @@ Library xml >= 1.3.12 && < 1.4, random >= 1 && < 1.2, extensible-exceptions >= 0.1 && < 0.2, - pandoc-types >= 1.12.4 && < 1.13, + pandoc-types >= 1.14 && < 1.15, aeson >= 0.7 && < 0.10, tagsoup >= 0.13.1 && < 0.14, base64-bytestring >= 0.1 && < 1.1, @@ -399,7 +399,7 @@ Library Executable pandoc Build-Depends: pandoc, - pandoc-types >= 1.12.4 && < 1.13, + pandoc-types >= 1.14 && < 1.15, base >= 4.2 && <5, directory >= 1 && < 1.3, filepath >= 1.1 && < 1.5, @@ -446,7 +446,7 @@ Test-Suite test-pandoc Build-Depends: base >= 4.2 && < 5, syb >= 0.1 && < 0.6, pandoc, - pandoc-types >= 1.12.4 && < 1.13, + pandoc-types >= 1.14 && < 1.15, bytestring >= 0.9 && < 0.11, text >= 0.11 && < 1.3, directory >= 1 && < 1.3, From 878ab00233ec57270a60103b2b152f2257c40bae Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 2 Apr 2015 21:02:39 -0700 Subject: [PATCH 04/14] ImageSize: Added functions for converting between image dimensions. (mb21) --- src/Text/Pandoc/ImageSize.hs | 153 +++++++++++++++++++++++++++++++---- 1 file changed, 138 insertions(+), 15 deletions(-) diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs index 09c1dd443..7489afc8e 100644 --- a/src/Text/Pandoc/ImageSize.hs +++ b/src/Text/Pandoc/ImageSize.hs @@ -29,17 +29,37 @@ Portability : portable Functions for determining the size of a PNG, JPEG, or GIF image. -} -module Text.Pandoc.ImageSize ( ImageType(..), imageType, imageSize, - sizeInPixels, sizeInPoints ) where +module Text.Pandoc.ImageSize ( ImageType(..) + , imageType + , imageSize + , sizeInPixels + , sizeInPoints + , desiredSizeInPoints + , Dimension(..) + , Direction(..) + , dimension + , inInch + , inPoints + , numUnit + , showInInch + , showInPixel + , showFl + ) where import Data.ByteString (ByteString, unpack) import qualified Data.ByteString.Char8 as B import qualified Data.ByteString.Lazy as BL +import Data.Char (isDigit) import Control.Applicative import Control.Monad import Data.Bits import Data.Binary import Data.Binary.Get 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 Text.Pandoc.Compat.Except import Control.Monad.Trans @@ -49,6 +69,20 @@ import Data.Maybe (fromMaybe) -- algorithms borrowed from wwwis.pl 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{ pxX :: Integer @@ -56,7 +90,11 @@ data ImageSize = ImageSize{ , dpiX :: Integer , dpiY :: Integer } 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 img = case B.take 4 img of @@ -88,8 +126,93 @@ defaultSize = (72, 72) sizeInPixels :: ImageSize -> (Integer, Integer) sizeInPixels s = (pxX s, pxY s) -sizeInPoints :: ImageSize -> (Integer, Integer) -sizeInPoints s = (pxX s * 72 `div` dpiX s, pxY s * 72 `div` dpiY s) +-- | Calculate (height, width) in points using the image file's dpi metadata, +-- 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 img = do @@ -279,21 +402,21 @@ exifHeader hdr = do return (tag, payload) entries <- sequence $ replicate (fromIntegral numentries) ifdEntry subentries <- case lookup ExifOffset entries of - Just (UnsignedLong offset) -> do + Just (UnsignedLong offset') -> do pos <- lift bytesRead - lift $ skip (fromIntegral offset - (fromIntegral pos - 8)) + lift $ skip (fromIntegral offset' - (fromIntegral pos - 8)) numsubentries <- lift getWord16 sequence $ replicate (fromIntegral numsubentries) ifdEntry _ -> return [] let allentries = entries ++ subentries - (width, height) <- case (lookup ExifImageWidth allentries, - lookup ExifImageHeight allentries) of - (Just (UnsignedLong w), Just (UnsignedLong h)) -> - return (fromIntegral w, fromIntegral h) - _ -> return defaultSize - -- we return a default width and height when - -- the exif header doesn't contain these + (wdth, hght) <- case (lookup ExifImageWidth allentries, + lookup ExifImageHeight allentries) of + (Just (UnsignedLong w), Just (UnsignedLong h)) -> + return (fromIntegral w, fromIntegral h) + _ -> return defaultSize + -- we return a default width and height when + -- the exif header doesn't contain these let resfactor = case lookup ResolutionUnit allentries of Just (UnsignedShort 1) -> (100 / 254) _ -> 1 @@ -302,8 +425,8 @@ exifHeader hdr = do let yres = maybe 72 (\(UnsignedRational x) -> floor $ x * resfactor) $ lookup YResolution allentries return $ ImageSize{ - pxX = width - , pxY = height + pxX = wdth + , pxY = hght , dpiX = xres , dpiY = yres } From 76f0708ef5bf06147b044f0b10eb50f43e042071 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 2 Apr 2015 21:04:12 -0700 Subject: [PATCH 05/14] Parsing: Add `extractIdClass`, modified type of `KeyTable`. (mb21) --- src/Text/Pandoc/Parsing.hs | 16 ++++++++++++++-- 1 file changed, 14 insertions(+), 2 deletions(-) diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index c316e9220..6b9565a51 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -164,7 +164,8 @@ module Text.Pandoc.Parsing ( anyLine, setSourceLine, newPos, addWarning, - (<+?>) + (<+?>), + extractIdClass ) where @@ -1067,7 +1068,7 @@ toKey = Key . map toLower . unwords . words . unbracket where unbracket ('[':xs) | "]" `isSuffixOf` xs = take (length xs - 1) xs unbracket xs = xs -type KeyTable = M.Map Key Target +type KeyTable = M.Map Key (Target, Attr) type SubstTable = M.Map Key Inlines @@ -1264,3 +1265,14 @@ addWarning mbpos msg = infixr 5 <+?> (<+?>) :: (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) . (<>) + +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 From 12df4054ad550641abe9817421282f3f6079fbfe Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 2 Apr 2015 21:04:43 -0700 Subject: [PATCH 06/14] PDF: Modified for new image size attributes parameter. (mb21) --- src/Text/Pandoc/PDF.hs | 12 ++++++------ 1 file changed, 6 insertions(+), 6 deletions(-) diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index 8f92a3321..25a90f08f 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -84,10 +84,10 @@ handleImage' :: WriterOptions -> FilePath -> Inline -> IO Inline -handleImage' opts tmpdir (Image ils (src,tit)) = do +handleImage' opts tmpdir (Image attr ils (src,tit)) = do exists <- doesFileExist src if exists - then return $ Image ils (src,tit) + then return $ Image attr ils (src,tit) else do res <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src case res of @@ -97,20 +97,20 @@ handleImage' opts tmpdir (Image ils (src,tit)) = do let basename = showDigest $ sha1 $ BL.fromChunks [contents] let fname = tmpdir basename <.> ext BS.writeFile fname contents - return $ Image ils (fname,tit) + return $ Image attr ils (fname,tit) _ -> do warn $ "Could not find image `" ++ src ++ "', skipping..." - return $ Image ils (src,tit) + return $ Image attr ils (src,tit) handleImage' _ _ x = return x convertImages :: FilePath -> Inline -> IO Inline -convertImages tmpdir (Image ils (src, tit)) = do +convertImages tmpdir (Image attr ils (src, tit)) = do img <- convertImage tmpdir src newPath <- case img of Left e -> src <$ warn e Right fp -> return fp - return (Image ils (newPath, tit)) + return (Image attr ils (newPath, tit)) convertImages _ x = return x -- Convert formats which do not work well in pdf to png From 4391c5f34cb0013dcc2f2b2f4e642d0b24ebc4b5 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 1 Apr 2015 15:50:54 -0700 Subject: [PATCH 07/14] ICML writer: Add Cite style to citations. (mb21) --- src/Text/Pandoc/Writers/ICML.hs | 4 +++- 1 file changed, 3 insertions(+), 1 deletion(-) diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 08e3e5b63..2eeccba3a 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -91,6 +91,7 @@ lowerAlphaName :: String upperAlphaName :: String subListParName :: String footnoteName :: String +citeName :: String paragraphName = "Paragraph" codeBlockName = "CodeBlock" blockQuoteName = "Blockquote" @@ -113,6 +114,7 @@ lowerAlphaName = "lowerAlpha" upperAlphaName = "upperAlpha" subListParName = "subParagraph" footnoteName = "Footnote" +citeName = "Cite" -- | Convert Pandoc document to string in ICML format. @@ -407,7 +409,7 @@ inlineToICML opts style (Subscript lst) = inlinesToICML opts (subscriptName:styl 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 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 Space = charStyle style space inlineToICML _ style LineBreak = charStyle style $ text lineSeparator From 9deb335ca5fbf9f1db0cd1d046d2b59a9a5a55fe Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 2 Apr 2015 21:06:51 -0700 Subject: [PATCH 08/14] ICML writer: changed type of `writeICML`. API change: It is now `WriterOptions -> Pandoc -> IO String`. Also handle new image attributes. (mb21) --- src/Text/Pandoc.hs | 2 +- src/Text/Pandoc/Writers/ICML.hs | 89 ++++++++++++++++++--------------- 2 files changed, 51 insertions(+), 40 deletions(-) diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index a4d963221..f9d19d9dd 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -273,7 +273,7 @@ writers = [ ,("html" , PureStringWriter writeHtmlString) ,("html5" , PureStringWriter $ \o -> writeHtmlString o{ writerHtml5 = True }) - ,("icml" , PureStringWriter writeICML) + ,("icml" , IOStringWriter writeICML) ,("s5" , PureStringWriter $ \o -> writeHtmlString o{ writerSlideVariant = S5Slides , writerTableOfContents = False }) diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 2eeccba3a..71e541b6f 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -17,15 +17,17 @@ module Text.Pandoc.Writers.ICML (writeICML) where import Text.Pandoc.Definition import Text.Pandoc.XML import Text.Pandoc.Writers.Shared -import Text.Pandoc.Shared (splitBy) +import Text.Pandoc.Shared (splitBy, fetchItem, warn) import Text.Pandoc.Options import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Pretty +import Text.Pandoc.ImageSize import Data.List (isPrefixOf, isInfixOf, stripPrefix) import Data.Text as Text (breakOnAll, pack) import Data.Monoid (mappend) import Control.Monad.State import Network.URI (isURI) +import System.FilePath (pathSeparator) import qualified Data.Set as Set type Style = [String] @@ -39,7 +41,7 @@ data WriterState = WriterState{ , maxListDepth :: Int } -type WS a = State WriterState a +type WS a = StateT WriterState IO a defaultWriterState :: WriterState defaultWriterState = WriterState{ @@ -118,27 +120,27 @@ citeName = "Cite" -- | Convert Pandoc document to string in ICML format. -writeICML :: WriterOptions -> Pandoc -> String -writeICML opts (Pandoc meta blocks) = +writeICML :: WriterOptions -> Pandoc -> IO String +writeICML opts (Pandoc meta blocks) = do let colwidth = if writerWrapText opts then Just $ writerColumns opts else Nothing render' = render colwidth - renderMeta f s = Just $ render' $ fst $ runState (f opts [] s) defaultWriterState - Just metadata = metaToJSON opts - (renderMeta blocksToICML) - (renderMeta inlinesToICML) - meta - (doc, st) = runState (blocksToICML opts [] blocks) defaultWriterState - main = render' doc + renderMeta f s = liftM (render' . fst) $ runStateT (f opts [] s) defaultWriterState + metadata <- metaToJSON opts + (renderMeta blocksToICML) + (renderMeta inlinesToICML) + meta + (doc, st) <- runStateT (blocksToICML opts [] blocks) defaultWriterState + let main = render' doc context = defField "body" main $ defField "charStyles" (render' $ charStylesToDoc st) $ defField "parStyles" (render' $ parStylesToDoc st) $ defField "hyperlinks" (render' $ hyperlinksToDoc $ links st) $ metadata - in if writerStandalone opts - then renderTemplate' (writerTemplate opts) context - else main + return $ if writerStandalone opts + then renderTemplate' (writerTemplate opts) context + else main -- | Auxilary functions for parStylesToDoc and charStylesToDoc. contains :: String -> (String, (String, String)) -> [(String, String)] @@ -427,7 +429,7 @@ inlineToICML opts style (Link lst (url, title)) = do cont = inTags True "HyperlinkTextSource" [("Self","htss-"++show ident), ("Name",title), ("Hidden","false")] content 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 (Span _ lst) = inlinesToICML opts style lst @@ -500,39 +502,48 @@ styleToStrAttr style = in (stlStr, attrs) -- | Assemble an ICML Image. -imageICML :: WriterOptions -> Style -> [Inline] -> Target -> WS Doc -imageICML _ style _ (linkURI, _) = - let imgWidth = 300::Int --TODO: set width, height dynamically as in Docx.hs - imgHeight = 200::Int - scaleFact = show (1::Double) --TODO: set scaling factor so image is scaled exactly to imgWidth x imgHeight - hw = show $ imgWidth `div` 2 - hh = show $ imgHeight `div` 2 - qw = show $ imgWidth `div` 4 - qh = show $ imgHeight `div` 4 - uriPrefix = if isURI linkURI then "" else "file:" +imageICML :: WriterOptions -> Style -> Attr -> [Inline] -> Target -> WS Doc +imageICML opts style attr _ (src, _) = do + res <- liftIO $ fetchItem (writerSourceURL opts) src + imgS <- case res of + Left (_) -> do + liftIO $ warn $ "Could not find image `" ++ src ++ "', skipping..." + return def + Right (img, _) -> do + case imageSize img of + 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 props = inTags True "Properties" [] $ inTags True "PathGeometry" [] $ inTags True "GeometryPathType" [("PathOpen","false")] $ inTags True "PathPointArray" [] $ vcat [ - selfClosingTag "PathPointType" [("Anchor", "-"++qw++" -"++qh), - ("LeftDirection", "-"++qw++" -"++qh), ("RightDirection", "-"++qw++" -"++qh)] - , selfClosingTag "PathPointType" [("Anchor", "-"++qw++" "++qh), - ("LeftDirection", "-"++qw++" "++qh), ("RightDirection", "-"++qw++" "++qh)] - , selfClosingTag "PathPointType" [("Anchor", qw++" "++qh), - ("LeftDirection", qw++" "++qh), ("RightDirection", qw++" "++qh)] - , selfClosingTag "PathPointType" [("Anchor", qw++" -"++qh), - ("LeftDirection", qw++" -"++qh), ("RightDirection", qw++" -"++qh)] + selfClosingTag "PathPointType" [("Anchor", "-"++hw++" -"++hh), + ("LeftDirection", "-"++hw++" -"++hh), ("RightDirection", "-"++hw++" -"++hh)] + , selfClosingTag "PathPointType" [("Anchor", "-"++hw++" "++hh), + ("LeftDirection", "-"++hw++" "++hh), ("RightDirection", "-"++hw++" "++hh)] + , selfClosingTag "PathPointType" [("Anchor", hw++" "++hh), + ("LeftDirection", hw++" "++hh), ("RightDirection", hw++" "++hh)] + , selfClosingTag "PathPointType" [("Anchor", hw++" -"++hh), + ("LeftDirection", hw++" -"++hh), ("RightDirection", hw++" -"++hh)] ] image = inTags True "Image" - [("Self","ue6"), ("ItemTransform", scaleFact++" 0 0 "++scaleFact++" -"++qw++" -"++qh)] + [("Self","ue6"), ("ItemTransform", scale++" -"++hw++" -"++hh)] $ vcat [ 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", uriPrefix++linkURI)] + , selfClosingTag "Link" [("Self", "ueb"), ("LinkResourceURI", src')] ] 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) - in do - state $ \st -> (doc, st{ inlineStyles = Set.insert stlStr $ inlineStyles st } ) + state $ \st -> (doc, st{ inlineStyles = Set.insert stlStr $ inlineStyles st } ) From 92d48fa65bb8b90f6d6b81646a15ce8326083f05 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 2 Apr 2015 21:09:08 -0700 Subject: [PATCH 09/14] Updated readers and writers for new image attribute parameter. (mb21) --- src/Text/Pandoc/Readers/CommonMark.hs | 2 +- src/Text/Pandoc/Readers/DocBook.hs | 21 ++++++--- src/Text/Pandoc/Readers/EPUB.hs | 4 +- src/Text/Pandoc/Readers/HTML.hs | 8 +++- src/Text/Pandoc/Readers/LaTeX.hs | 29 ++++++++---- src/Text/Pandoc/Readers/Markdown.hs | 55 ++++++++++++---------- src/Text/Pandoc/Readers/MediaWiki.hs | 30 +++++++----- src/Text/Pandoc/Readers/RST.hs | 18 +++---- src/Text/Pandoc/Shared.hs | 4 +- src/Text/Pandoc/Writers/AsciiDoc.hs | 22 +++++++-- src/Text/Pandoc/Writers/CommonMark.hs | 2 +- src/Text/Pandoc/Writers/ConTeXt.hs | 38 ++++++++++++--- src/Text/Pandoc/Writers/Custom.hs | 4 +- src/Text/Pandoc/Writers/Docbook.hs | 25 ++++++++-- src/Text/Pandoc/Writers/Docx.hs | 20 ++++---- src/Text/Pandoc/Writers/DokuWiki.hs | 20 ++++++-- src/Text/Pandoc/Writers/EPUB.hs | 4 +- src/Text/Pandoc/Writers/FB2.hs | 12 ++--- src/Text/Pandoc/Writers/HTML.hs | 44 ++++++++++++++---- src/Text/Pandoc/Writers/Haddock.hs | 6 +-- src/Text/Pandoc/Writers/LaTeX.hs | 35 +++++++++++--- src/Text/Pandoc/Writers/Man.hs | 2 +- src/Text/Pandoc/Writers/Markdown.hs | 12 +++-- src/Text/Pandoc/Writers/MediaWiki.hs | 31 +++++++++++-- src/Text/Pandoc/Writers/ODT.hs | 17 +++---- src/Text/Pandoc/Writers/OpenDocument.hs | 14 +++--- src/Text/Pandoc/Writers/Org.hs | 6 +-- src/Text/Pandoc/Writers/RST.hs | 62 ++++++++++++++++++------- src/Text/Pandoc/Writers/RTF.hs | 12 ++--- src/Text/Pandoc/Writers/Texinfo.hs | 21 ++++++--- src/Text/Pandoc/Writers/Textile.hs | 23 +++++++-- 31 files changed, 415 insertions(+), 188 deletions(-) diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs index 51a35c8ad..9112979ab 100644 --- a/src/Text/Pandoc/Readers/CommonMark.hs +++ b/src/Text/Pandoc/Readers/CommonMark.hs @@ -115,5 +115,5 @@ addInline (Node _ STRONG nodes) = addInline (Node _ (LINK url title) nodes) = (Link (addInlines nodes) (unpack url, unpack title) :) addInline (Node _ (IMAGE url title) nodes) = - (Image (addInlines nodes) (unpack url, unpack title) :) + (Image nullAttr (addInlines nodes) (unpack url, unpack title) :) addInline _ = id diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index 3cc2a4479..cbd50c252 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -633,11 +633,20 @@ addToStart toadd bs = -- A DocBook mediaobject is a wrapper around a set of alternative presentations getMediaobject :: Element -> DB Inlines getMediaobject e = do - imageUrl <- case filterChild (named "imageobject") e of - Nothing -> return mempty - Just z -> case filterChild (named "imagedata") z of - Nothing -> return mempty - Just i -> return $ attrValue "fileref" i + (imageUrl, attr) <- + case filterChild (named "imageobject") e of + Nothing -> return (mempty, nullAttr) + Just z -> case filterChild (named "imagedata") z of + Nothing -> return (mempty, nullAttr) + 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 || named "textobject" x || named "alt" x) el of @@ -647,7 +656,7 @@ getMediaobject e = do let (caption, title) = if isNull figTitle then (getCaption e, "") else (return figTitle, "fig:") - liftM (image imageUrl title) caption + liftM (imageWith imageUrl title attr) caption getBlocks :: Element -> DB Blocks getBlocks e = mconcat <$> (mapM parseBlock $ elContent e) diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs index 338540533..04edf4c6a 100644 --- a/src/Text/Pandoc/Readers/EPUB.hs +++ b/src/Text/Pandoc/Readers/EPUB.hs @@ -101,12 +101,12 @@ fetchImages mimes root arc (query iq -> links) = <$> findEntryByPath abslink arc iq :: Inline -> [FilePath] -iq (Image _ (url, _)) = [url] +iq (Image _ _ (url, _)) = [url] iq _ = [] -- Remove relative paths 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 imageToPandoc :: FilePath -> Pandoc diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index fcba16e04..d0ee893f2 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -609,7 +609,13 @@ pImage = do _ -> url' let title = fromAttrib "title" 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 (escapeURI url) title (uid, cls, kvs) (B.text alt) pCode :: TagParser Inlines pCode = try $ do diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 0da912ea6..def429232 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -55,6 +55,7 @@ import Data.List (intercalate) import qualified Data.Map as M import qualified Control.Exception as E import Text.Pandoc.Highlighting (fromListingsLanguage) +import Text.Pandoc.ImageSize (numUnit, showFl) import Text.Pandoc.Error -- | Parse LaTeX from string and return 'Pandoc' document. @@ -391,7 +392,8 @@ inlineCommand = try $ do star <- option "" (string "*") let name' = name ++ star let raw = do - rawcommand <- getRawCommand name' + rawargs <- withRaw (skipopts *> option "" dimenarg *> many braced) + let rawcommand = '\\' : name ++ star ++ snd rawargs transformed <- applyMacros' rawcommand if transformed /= rawcommand then parseFromString inlines transformed @@ -521,7 +523,9 @@ inlineCommands = M.fromList $ , ("href", (unescapeURL <$> braced <* optional sp) >>= \url -> tok >>= \lab -> pure (link url "" lab)) - , ("includegraphics", skipopts *> (unescapeURL <$> braced) >>= mkImage) + , ("includegraphics", do options <- option [] keyvals + src <- unescapeURL <$> braced + mkImage options src) , ("enquote", enquote) , ("cite", citation "cite" AuthorInText False) , ("citep", citation "citep" NormalCitation False) @@ -582,14 +586,19 @@ inlineCommands = M.fromList $ -- in which case they will appear as raw latex blocks: [ "index" ] -mkImage :: String -> LP Inlines -mkImage src = do +mkImage :: [(String, String)] -> String -> LP Inlines +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" case takeExtension src of "" -> do defaultExt <- getOption readerDefaultImageExtension - return $ image (addExtension src defaultExt) "" alt - _ -> return $ image src "" alt + return $ imageWith (addExtension src defaultExt) "" attr alt + _ -> return $ imageWith src "" attr alt inNote :: Inlines -> Inlines inNote ils = @@ -970,7 +979,7 @@ readFileFromDirs (d:ds) f = keyval :: LP (String, String) keyval = try $ do key <- many1 alphaNum - val <- option "" $ char '=' >> many1 alphaNum + val <- option "" $ char '=' >> many1 (alphaNum <|> char '.' <|> char '\\') skipMany spaceChar optional (char ',') skipMany spaceChar @@ -997,11 +1006,11 @@ rawLaTeXInline = do addImageCaption :: Blocks -> LP Blocks addImageCaption = walkM go - where go (Image alt (src,tit)) = do + where go (Image attr alt (src,tit)) = do mbcapt <- stateCaption <$> getState return $ case mbcapt of - Just ils -> Image (toList ils) (src, "fig:") - Nothing -> Image alt (src,tit) + Just ils -> Image attr (toList ils) (src, "fig:") + Nothing -> Image attr alt (src,tit) go x = return x addTableCaption :: Blocks -> LP Blocks diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index ea5f5326d..ebca7e83d 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -369,23 +369,26 @@ referenceKey = try $ do let sourceURL = liftM unwords $ many $ try $ do skipMany spaceChar notFollowedBy' referenceTitle + notFollowedBy' $ guardEnabled Ext_common_link_attributes >> attributes notFollowedBy' (() <$ reference) many1 $ notFollowedBy space >> litChar let betweenAngles = try $ char '<' >> manyTill litChar (char '>') src <- try betweenAngles <|> sourceURL tit <- option "" referenceTitle - -- currently we just ignore MMD-style link/image attributes - _kvs <- option [] $ guardEnabled Ext_link_attributes - >> many (try $ spnl >> keyValAttr) + attr <- option nullAttr $ try $ + guardEnabled Ext_common_link_attributes >> skipSpaces >> attributes + addKvs <- option [] $ guardEnabled Ext_link_attributes + >> many (try $ spnl >> keyValAttr) blanklines - let target = (escapeURI $ trimr src, tit) + let attr' = extractIdClass $ foldl (\x f -> f x) attr addKvs + target = (escapeURI $ trimr src, tit) st <- getState let oldkeys = stateKeys st let key = toKey raw case M.lookup key oldkeys of Just _ -> addWarning (Just pos) $ "Duplicate link reference `" ++ raw ++ "'" Nothing -> return () - updateState $ \s -> s { stateKeys = M.insert key target oldkeys } + updateState $ \s -> s { stateKeys = M.insert key (target, attr') oldkeys } return $ return mempty referenceTitle :: MarkdownParser String @@ -512,9 +515,9 @@ atxHeader = try $ do (text, raw) <- withRaw $ trimInlinesF . mconcat <$> many (notFollowedBy atxClosing >> inline) attr <- atxClosing - attr'@(ident,_,_) <- registerHeader attr (runF text defaultParserState) + attr' <- registerHeader attr (runF text defaultParserState) guardDisabled Ext_implicit_header_references - <|> registerImplicitHeader raw ident + <|> registerImplicitHeader raw attr' return $ B.headerWith attr' level <$> text atxClosing :: MarkdownParser Attr @@ -555,16 +558,16 @@ setextHeader = try $ do many (char underlineChar) blanklines 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 - <|> registerImplicitHeader raw ident + <|> registerImplicitHeader raw attr' return $ B.headerWith attr' level <$> text -registerImplicitHeader :: String -> String -> MarkdownParser () -registerImplicitHeader raw ident = do +registerImplicitHeader :: String -> Attr -> MarkdownParser () +registerImplicitHeader raw attr@(ident, _, _) = do let key = toKey $ "[" ++ raw ++ "]" updateState (\s -> s { stateHeaderKeys = - M.insert key ('#':ident,"") (stateHeaderKeys s) }) + M.insert key (('#':ident,""), attr) (stateHeaderKeys s) }) -- -- hrule block @@ -971,11 +974,11 @@ para = try $ do return $ do result' <- result case B.toList result' of - [Image alt (src,tit)] + [Image attr alt (src,tit)] | Ext_implicit_figures `Set.member` exts -> -- the fig: at beginning of title indicates a figure return $ B.para $ B.singleton - $ Image alt (src,'f':'i':'g':':':tit) + $ Image attr alt (src,'f':'i':'g':':':tit) _ -> return $ B.para result' plain :: MarkdownParser (F Blocks) @@ -1700,16 +1703,18 @@ link = try $ do setState $ st{ stateAllowLinks = False } (lab,raw) <- reference 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 :: (String -> String -> Attr -> Inlines -> Inlines) -> F Inlines -> MarkdownParser (F Inlines) regLink constructor lab = try $ do (src, tit) <- source - return $ constructor src tit <$> lab + attr <- option nullAttr $ + guardEnabled Ext_common_link_attributes >> attributes + return $ constructor src tit attr <$> lab -- a link like [this][ref] or [this][] or [this] -referenceLink :: (String -> String -> Inlines -> Inlines) +referenceLink :: (String -> String -> Attr -> Inlines -> Inlines) -> (F Inlines, String) -> MarkdownParser (F Inlines) referenceLink constructor (lab, raw) = do sp <- (True <$ lookAhead (char ' ')) <|> return False @@ -1721,7 +1726,7 @@ referenceLink constructor (lab, raw) = do let labIsRef = raw' == "" || raw' == "[]" let key = toKey $ if labIsRef then raw else raw' parsedRaw <- parseFromString (mconcat <$> many inline) raw' - fallback <- parseFromString (mconcat <$> many inline) $ dropBrackets raw + fallback <- parseFromString (mconcat <$> many inline) $ dropBrackets raw implicitHeaderRefs <- option False $ True <$ guardEnabled Ext_implicit_header_references let makeFallback = do @@ -1738,10 +1743,10 @@ referenceLink constructor (lab, raw) = do then do headerKeys <- asksF stateHeaderKeys case M.lookup key headerKeys of - Just (src, tit) -> constructor src tit <$> lab - Nothing -> makeFallback + Just ((src, tit), _) -> constructor src tit nullAttr <$> lab + Nothing -> makeFallback else makeFallback - Just (src,tit) -> constructor src tit <$> lab + Just ((src,tit), attr) -> constructor src tit attr <$> lab dropBrackets :: String -> String dropBrackets = reverse . dropRB . reverse . dropLB @@ -1776,8 +1781,8 @@ image = try $ do (lab,raw) <- reference defaultExt <- getOption readerDefaultImageExtension let constructor src = case takeExtension src of - "" -> B.image (addExtension src defaultExt) - _ -> B.image src + "" -> B.imageWith (addExtension src defaultExt) + _ -> B.imageWith src regLink constructor lab <|> referenceLink constructor (lab,raw) note :: MarkdownParser (F Inlines) @@ -1913,7 +1918,7 @@ textualCite = try $ do spc | null spaces' = mempty | otherwise = B.space lab <- parseFromString (mconcat <$> many inline) $ dropBrackets raw' - fallback <- referenceLink B.link (lab,raw') + fallback <- referenceLink B.linkWith (lab,raw') return $ do fallback' <- fallback cs' <- cs diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index 2a5adab22..6f7da2586 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -577,21 +577,29 @@ image = try $ do sym "[[" choice imageIdentifiers 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 "]]") <|> try (char '|' *> (mconcat <$> manyTill inline (sym "]]"))) - return $ B.image fname ("fig:" ++ stringify caption) caption + return $ B.imageWith fname ("fig:" ++ stringify caption) attr caption imageOption :: MWParser String -imageOption = - try (oneOfStrings [ "border", "thumbnail", "frameless" - , "thumb", "upright", "left", "right" - , "center", "none", "baseline", "sub" - , "super", "top", "text-top", "middle" - , "bottom", "text-bottom" ]) - <|> try (string "frame") - <|> try (many1 (oneOf "x0123456789") <* string "px") - <|> try (oneOfStrings ["link=","alt=","page=","class="] <* many (noneOf "|]")) +imageOption = try $ char '|' *> opt + where + opt = try (oneOfStrings [ "border", "thumbnail", "frameless" + , "thumb", "upright", "left", "right" + , "center", "none", "baseline", "sub" + , "super", "top", "text-top", "middle" + , "bottom", "text-bottom" ]) + <|> try (string "frame") + <|> try (oneOfStrings ["link=","alt=","page=","class="] <* many (noneOf "|]")) collapseUnderscores :: String -> String collapseUnderscores [] = [] diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 678eecc52..8969c3176 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -812,9 +812,9 @@ substKey = try $ do res <- B.toList <$> directive' il <- case res of -- 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 - [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) [Para ils] -> return $ B.fromList ils _ -> mzero @@ -827,7 +827,8 @@ anonymousKey = try $ do src <- targetURI pos <- getPosition 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 = reverse . stripTick . reverse . stripTick @@ -841,7 +842,8 @@ regularKey = try $ do char ':' src <- targetURI 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 @@ -1131,12 +1133,12 @@ referenceLink = try $ do if null anonKeys then mzero else return (head anonKeys) - (src,tit) <- case M.lookup key keyTable of - Nothing -> fail "no corresponding key" - Just target -> return target + ((src,tit), attr) <- case M.lookup key keyTable of + Nothing -> fail "no corresponding key" + Just val -> return val -- if anonymous link, remove key so it won't be used again when (isAnonKey key) $ updateState $ \s -> s{ stateKeys = M.delete key keyTable } - return $ B.link src tit label' + return $ B.linkWith src tit attr label' autoURI :: RSTParser Inlines autoURI = do diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index c09c2f2a0..a816af8b9 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -509,8 +509,8 @@ normalizeInlines (Quoted qt ils : ys) = Quoted qt (normalizeInlines ils) : normalizeInlines ys normalizeInlines (Link ils t : ys) = Link (normalizeInlines ils) t : normalizeInlines ys -normalizeInlines (Image ils t : ys) = - Image (normalizeInlines ils) t : normalizeInlines ys +normalizeInlines (Image attr ils t : ys) = + Image attr (normalizeInlines ils) t : normalizeInlines ys normalizeInlines (Cite cs ils : ys) = Cite cs (normalizeInlines ils) : normalizeInlines ys normalizeInlines (x : xs) = x : normalizeInlines xs diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index bac28e54f..8b36ef5c6 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -46,6 +46,7 @@ import Text.Pandoc.Parsing hiding (blankline, space) import Data.Maybe (fromMaybe) import Data.List ( stripPrefix, intersperse, intercalate ) import Text.Pandoc.Pretty +import Text.Pandoc.ImageSize import Control.Monad.State import qualified Data.Map as M import Data.Aeson (Value(String), fromJSON, toJSON, Result(..)) @@ -127,8 +128,8 @@ blockToAsciiDoc _ Null = return empty blockToAsciiDoc opts (Plain inlines) = do contents <- inlineListToAsciiDoc opts inlines return $ contents <> blankline -blockToAsciiDoc opts (Para [Image alt (src,'f':'i':'g':':':tit)]) = do - blockToAsciiDoc opts (Para [Image alt (src,tit)]) +blockToAsciiDoc opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = do + blockToAsciiDoc opts (Para [Image attr alt (src,tit)]) blockToAsciiDoc opts (Para inlines) = do contents <- inlineListToAsciiDoc opts inlines -- escape if para starts with ordered list marker @@ -409,7 +410,7 @@ inlineToAsciiDoc opts (Link txt (src, _tit)) = do return $ if useAuto then text srcSuffix 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"] let txt = if (null alternate) || (alternate == [Str ""]) then [Str "image"] @@ -417,8 +418,19 @@ inlineToAsciiDoc opts (Image alternate (src, tit)) = do linktext <- inlineListToAsciiDoc opts txt let linktitle = if null tit then empty - else text $ ",title=\"" ++ tit ++ "\"" - return $ "image:" <> text src <> "[" <> linktext <> linktitle <> "]" + else ",title=\"" <> text tit <> "\"" + 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 [Plain inlines]) inlineToAsciiDoc opts (Note [Plain inlines]) = do diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs index fee36d454..c65b8de37 100644 --- a/src/Text/Pandoc/Writers/CommonMark.hs +++ b/src/Text/Pandoc/Writers/CommonMark.hs @@ -155,7 +155,7 @@ inlineToNodes (SmallCaps xs) = [node (INLINE_HTML (T.pack "")) []]) ++ ) inlineToNodes (Link ils (url,tit)) = (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) :) inlineToNodes (RawInline fmt xs) | fmt == Format "html" = (node (INLINE_HTML (T.pack xs)) [] :) diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 1f8bbcdba..97f61dac8 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -35,10 +35,11 @@ import Text.Pandoc.Writers.Shared import Text.Pandoc.Options import Text.Pandoc.Walk (query) import Text.Printf ( printf ) -import Data.List ( intercalate ) +import Data.List ( intercalate, intersperse ) import Data.Char ( ord ) import Control.Monad.State import Text.Pandoc.Pretty +import Text.Pandoc.ImageSize import Text.Pandoc.Templates ( renderTemplate' ) import Network.URI ( isURI, unEscapeString ) @@ -136,10 +137,14 @@ blockToConTeXt :: Block blockToConTeXt Null = return empty blockToConTeXt (Plain lst) = inlineListToConTeXt lst -- 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 - return $ blankline $$ "\\placefigure" <> braces capt <> - braces ("\\externalfigure" <> brackets (text src)) <> blankline + img <- inlineToConTeXt (Image attr txt (src, "")) + 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 contents <- inlineListToConTeXt lst return $ contents <> blankline @@ -321,11 +326,30 @@ inlineToConTeXt (Link txt (src, _)) = do else brackets empty <> brackets contents) <> "\\from" <> brackets (text ref) -inlineToConTeXt (Image _ (src, _)) = do - let src' = if isURI src +inlineToConTeXt (Image attr _ (src, _)) = do + opts <- gets stOptions + let (_,cls,_) = attr + 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 else unEscapeString src - return $ braces $ "\\externalfigure" <> brackets (text src') + return $ braces $ "\\externalfigure" <> brackets (text src') <> dims <> clas inlineToConTeXt (Note contents) = do contents' <- blockListToConTeXt contents let codeBlock x@(CodeBlock _ _) = [x] diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index 3a9c1954a..18b1bec5f 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -223,7 +223,7 @@ blockToCustom _ Null = return "" 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 blockToCustom lua (Para inlines) = callfunc lua "Para" inlines @@ -312,7 +312,7 @@ inlineToCustom lua (LineBreak) = callfunc lua "LineBreak" inlineToCustom 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 inlineToCustom lua (Note contents) = callfunc lua "Note" contents diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index f3b99e141..af289d45e 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -43,6 +43,7 @@ import Control.Applicative ((<$>)) import Data.Monoid ( Any(..) ) import Text.Pandoc.Highlighting ( languages, languagesByExtension ) import Text.Pandoc.Pretty +import Text.Pandoc.ImageSize import qualified Text.Pandoc.Builder as B import Text.TeXMath import qualified Text.XML.Light as Xml @@ -151,6 +152,22 @@ listItemToDocbook :: WriterOptions -> [Block] -> Doc listItemToDocbook opts item = inTagsIndented "listitem" $ blocksToDocbook opts $ map plainToPara item +imageToDocbook :: WriterOptions -> Attr -> String -> Doc +imageToDocbook _ attr src = selfClosingTag "imagedata" $ ("fileref", src):ident + ++ roles ++ dims + where + (idStr,cls,_) = attr + ident = if null idStr + then [] + else [("id", idStr)] + roles = if null cls + then [] + else [("role", unwords cls)] + 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. blockToDocbook :: WriterOptions -> Block -> Doc blockToDocbook _ Null = empty @@ -166,7 +183,7 @@ blockToDocbook opts (Div _ bs) = blocksToDocbook opts $ map plainToPara bs blockToDocbook _ (Header _ _ _) = empty -- should not occur after hierarchicalize blockToDocbook opts (Plain lst) = inlinesToDocbook opts lst -- 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 capt = if null txt then empty @@ -175,7 +192,7 @@ blockToDocbook opts (Para [Image txt (src,'f':'i':'g':':':_)]) = capt $$ (inTagsIndented "mediaobject" $ (inTagsIndented "imageobject" - (selfClosingTag "imagedata" [("fileref",src)])) $$ + (imageToDocbook opts attr src)) $$ inTagsSimple "textobject" (inTagsSimple "phrase" alt)) blockToDocbook opts (Para lst) | hasLineBreaks lst = flush $ nowrap $ inTagsSimple "literallayout" $ inlinesToDocbook opts lst @@ -335,13 +352,13 @@ inlineToDocbook opts (Link txt (src, _)) then inTags False "link" [("linkend", drop 1 src)] else inTags False "ulink" [("url", src)]) $ inlinesToDocbook opts txt -inlineToDocbook _ (Image _ (src, tit)) = +inlineToDocbook opts (Image attr _ (src, tit)) = let titleDoc = if null tit then empty else inTagsIndented "objectinfo" $ inTagsIndented "title" (text $ escapeStringForXML tit) in inTagsIndented "inlinemediaobject" $ inTagsIndented "imageobject" $ - titleDoc $$ selfClosingTag "imagedata" [("fileref", src)] + titleDoc $$ imageToDocbook opts attr src inlineToDocbook opts (Note contents) = inTagsIndented "footnote" $ blocksToDocbook opts contents diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index da4c78cef..a17be3ca0 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -537,7 +537,6 @@ styleToOpenXml sm style = , mknode "w:link" [("w:val","VerbatimChar")] () , mknode "w:pPr" [] $ mknode "w:wordWrap" [("w:val","off")] () - : mknode "w:noProof" [] () : ( maybe [] (\col -> [mknode "w:shd" [("w:val","clear"),("w:fill",drop 1 $ fromColor col)] ()]) $ backgroundColor style ) ] @@ -753,7 +752,7 @@ blockToOpenXML opts (Header lev (ident,_,_) lst) = do blockToOpenXML opts (Plain lst) = withParaProp (pCustomStyle "Compact") $ blockToOpenXML opts (Para lst) -- 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 pushParaProp $ pCustomStyle $ if null alt @@ -761,7 +760,7 @@ blockToOpenXML opts (Para [Image alt (src,'f':'i':'g':':':tit)]) = do else "FigureWithCaption" paraProps <- getParaProps False popParaProp - contents <- inlinesToOpenXML opts [Image alt (src,tit)] + contents <- inlinesToOpenXML opts [Image attr alt (src,tit)] captionNode <- withParaProp (pCustomStyle "ImageCaption") $ blockToOpenXML opts (Para alt) return $ mknode "w:p" [] (paraProps ++ contents) : captionNode @@ -1103,7 +1102,7 @@ inlineToOpenXML opts (Link txt (src,_)) = do M.insert src i extlinks } return i 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 pageWidth <- gets stPrintWidth imgs <- gets stImages @@ -1120,7 +1119,8 @@ inlineToOpenXML opts (Image alt (src, tit)) = do Right (img, mt) -> do ident <- ("rId"++) `fmap` getUniqueId (xpt,ypt) <- case imageSize img of - Right size -> return $ sizeInPoints size + Right size -> return $ + desiredSizeInPoints opts attr size Left msg -> do liftIO $ warn $ "Could not determine image size in `" ++ @@ -1212,11 +1212,9 @@ parseXml refArchive distArchive relpath = -- | Scales the image to fit the page -- sizes are passed in emu -fitToPage :: (Integer, Integer) -> Integer -> (Integer, Integer) +fitToPage :: (Double, Double) -> Integer -> (Integer, Integer) fitToPage (x, y) pageWidth -- Fixes width to the page width and scales the height - | x > pageWidth = - (pageWidth, round $ - ((fromIntegral pageWidth) / ((fromIntegral :: Integer -> Double) x)) * (fromIntegral y)) - | otherwise = (x, y) - + | x > fromIntegral pageWidth = + (pageWidth, floor $ ((fromIntegral pageWidth) / x) * y) + | otherwise = (floor x, floor y) diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 7ebe09db7..915821050 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -47,6 +47,7 @@ import Text.Pandoc.Options ( WriterOptions( import Text.Pandoc.Shared ( escapeURI, removeFormatting, camelCaseToHyphenated , trimr, normalize, substitute ) import Text.Pandoc.Writers.Shared ( defField, metaToJSON ) +import Text.Pandoc.ImageSize import Text.Pandoc.Templates ( renderTemplate' ) import Data.List ( intersect, intercalate, isPrefixOf, transpose ) import Data.Default (Default(..)) @@ -127,7 +128,7 @@ blockToDokuWiki opts (Plain inlines) = -- title beginning with fig: indicates that the image is a figure -- 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 then return "" else (" " ++) `fmap` inlineListToDokuWiki opts txt @@ -136,7 +137,7 @@ blockToDokuWiki opts (Para [Image txt (src,'f':'i':'g':':':tit)]) = do else "|" ++ if null tit then capt else tit ++ capt -- Relative links fail isURI and receive a colon prefix = if isURI src then "" else ":" - return $ "{{" ++ prefix ++ src ++ opt ++ "}}\n" + return $ "{{" ++ prefix ++ src ++ imageDims opts attr ++ opt ++ "}}\n" blockToDokuWiki opts (Para inlines) = do indent <- stIndent <$> ask @@ -474,7 +475,7 @@ inlineToDokuWiki opts (Link txt (src, _)) = do where src' = case src of '/':xs -> xs -- with leading / it's a _ -> 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 let txt = case (tit, alt) of ("", []) -> "" @@ -482,10 +483,21 @@ inlineToDokuWiki opts (Image alt (source, tit)) = do (_ , _ ) -> "|" ++ tit -- Relative links fail isURI and receive a colon prefix = if isURI source then "" else ":" - return $ "{{" ++ prefix ++ source ++ txt ++ "}}" + return $ "{{" ++ prefix ++ source ++ imageDims opts attr ++ txt ++ "}}" inlineToDokuWiki opts (Note contents) = do contents' <- blockListToDokuWiki opts contents modify (\s -> s { stNotes = True }) return $ "((" ++ contents' ++ "))" -- 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 = "" diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 8577c0fa2..950d5cde3 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -871,9 +871,9 @@ transformInline :: WriterOptions -> IORef [(FilePath, (FilePath, Maybe Entry))] -- ^ (oldpath, newpath) media -> 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 - return $ Image lab (newsrc, tit) + return $ Image attr lab (newsrc, tit) transformInline opts _ (x@(Math _ _)) | WebTeX _ <- writerHTMLMathMethod opts = do raw <- makeSelfContained opts $ writeHtmlInline opts x diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 31fa4bee8..f8f007185 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -314,8 +314,8 @@ blockToXml :: Block -> FBM [Content] blockToXml (Plain ss) = cMapM toXml ss -- FIXME: can lead to malformed FB2 blockToXml (Para [Math DisplayMath formula]) = insertMath NormalImage formula -- title beginning with fig: indicates that the image is a figure -blockToXml (Para [Image alt (src,'f':'i':'g':':':tit)]) = - insertImage NormalImage (Image alt (src,tit)) +blockToXml (Para [Image atr alt (src,'f':'i':'g':':':tit)]) = + insertImage NormalImage (Image atr alt (src,tit)) blockToXml (Para ss) = liftM (list . el "p") $ cMapM toXml ss blockToXml (CodeBlock _ s) = return . spaceBeforeAfter . map (el "p" . el "code") . lines $ s @@ -459,7 +459,7 @@ toXml (Link text (url,ttl)) = do ( [ attr ("l","href") ('#':ln_id) , uattr "type" "note" ] , ln_ref) ] -toXml img@(Image _ _) = insertImage InlineImage img +toXml img@(Image _ _ _) = insertImage InlineImage img toXml (Note bs) = do fns <- footnotes `liftM` get let n = 1 + length fns @@ -478,12 +478,12 @@ insertMath immode formula = do WebTeX url -> do let alt = [Code nullAttr formula] let imgurl = url ++ urlEncode formula - let img = Image alt (imgurl, "") + let img = Image nullAttr alt (imgurl, "") insertImage immode img _ -> return [el "code" formula] insertImage :: ImageMode -> Inline -> FBM [Content] -insertImage immode (Image alt (url,ttl)) = do +insertImage immode (Image _ alt (url,ttl)) = do images <- imagesToFetch `liftM` get let n = 1 + length images let fname = "image" ++ show n @@ -573,7 +573,7 @@ plain LineBreak = "\n" plain (Math _ s) = s plain (RawInline _ s) = s 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 -- | Create an XML element. diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index a2778ea97..436c5b343 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -34,6 +34,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared import Text.Pandoc.Options +import Text.Pandoc.ImageSize import Text.Pandoc.Templates import Text.Pandoc.Readers.TeXMath import Text.Pandoc.Slides @@ -407,11 +408,33 @@ obfuscateString = concatMap obfuscateChar . fromEntities addAttrs :: WriterOptions -> Attr -> Html -> Html 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 opts (id',classes',keyvals) = [prefixedId opts id' | not (null id')] ++ - [A.class_ (toValue $ unwords classes') | not (null classes')] ++ - map (\(x,y) -> customAttribute (fromString x) (toValue y)) keyvals + [A.class_ (toValue $ unwords classes') | not (null classes')] ++ toAttrs 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 = [ "art", "bmp", "cdr", "cdt", "cpt", "cr2", "crw", "djvu", "erf", @@ -432,8 +455,8 @@ blockToHtml :: WriterOptions -> Block -> State WriterState Html blockToHtml _ Null = return mempty blockToHtml opts (Plain lst) = inlineListToHtml opts lst -- title beginning with fig: indicates that the image is a figure -blockToHtml opts (Para [Image txt (s,'f':'i':'g':':':tit)]) = do - img <- inlineToHtml opts (Image txt (s,tit)) +blockToHtml opts (Para [Image attr txt (s,'f':'i':'g':':':tit)]) = do + img <- inlineToHtml opts (Image attr txt (s,tit)) let tocapt = if writerHtml5 opts then H5.figcaption else H.p ! A.class_ "caption" @@ -801,16 +824,19 @@ inlineToHtml opts inline = return $ if null tit then link' 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] ++ - [A.title $ toValue tit | not $ null tit] ++ - [A.alt $ toValue $ stringify txt] + [A.title $ toValue tit | not (null tit)] ++ + [A.alt $ toValue alternate' | not (null txt)] ++ + imgAttrsToHtml opts attr let tag = if writerHtml5 opts then H5.img else H.img return $ foldl (!) tag attributes -- note: null title included, as in Markdown.pl - (Image _ (s,tit)) -> do + (Image attr _ (s,tit)) -> do 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 -- note: null title included, as in Markdown.pl (Note contents) diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 14f398da9..49a9953b6 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -103,8 +103,8 @@ blockToHaddock opts (Plain inlines) = do contents <- inlineListToHaddock opts inlines return $ contents <> cr -- title beginning with fig: indicates figure -blockToHaddock opts (Para [Image alt (src,'f':'i':'g':':':tit)]) = - blockToHaddock opts (Para [Image alt (src,tit)]) +blockToHaddock opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = + blockToHaddock opts (Para [Image attr alt (src,tit)]) blockToHaddock opts (Para inlines) = -- TODO: if it contains linebreaks, we need to use a @...@ block (<> blankline) `fmap` blockToHaddock opts (Plain inlines) @@ -335,7 +335,7 @@ inlineToHaddock opts (Link txt (src, _)) = do _ -> False return $ nowrap $ "<" <> text src <> (if useAuto then empty else space <> linktext) <> ">" -inlineToHaddock opts (Image alternate (source, tit)) = do +inlineToHaddock opts (Image _ alternate (source, tit)) = do linkhaddock <- inlineToHaddock opts (Link alternate (source, tit)) return $ "<" <> linkhaddock <> ">" -- haddock doesn't have notes, but we can fake it: diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 506edd182..76ad1c510 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -46,6 +46,7 @@ import Control.Applicative ((<|>)) import Control.Monad.State import qualified Text.Parsec as P import Text.Pandoc.Pretty +import Text.Pandoc.ImageSize import Text.Pandoc.Slides import Text.Pandoc.Highlighting (highlight, styleToLaTeX, formatLaTeXInline, formatLaTeXBlock, @@ -335,15 +336,20 @@ blockToLaTeX (Div (identifier,classes,_) bs) = do blockToLaTeX (Plain lst) = inlineListToLaTeX $ dropWhile isLineBreakOrSpace lst -- 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 capt <- inlineListToLaTeX txt - img <- inlineToLaTeX (Image txt (src,tit)) + img <- inlineToLaTeX (Image attr txt (src,tit)) + let (ident, _, _) = attr + idn <- toLabel ident + let label = if null ident + then empty + else "\\label" <> braces (text idn) return $ if inNote -- can't have figures in notes then "\\begin{center}" $$ img $+$ capt $$ "\\end{center}" else "\\begin{figure}[htbp]" $$ "\\centering" $$ img $$ - ("\\caption" <> braces capt) $$ "\\end{figure}" + ("\\caption" <> braces capt) $$ label $$ "\\end{figure}" -- . . . indicates pause in beamer slides blockToLaTeX (Para [Str ".",Space,Str ".",Space,Str "."]) = do beamer <- writerBeamer `fmap` gets stOptions @@ -843,16 +849,31 @@ inlineToLaTeX (Link txt (src, _)) = src' <- stringToLaTeX URLString src return $ text ("\\href{" ++ src' ++ "}{") <> contents <> char '}' -inlineToLaTeX (Image _ (source, _)) = do +inlineToLaTeX (Image attr _ (source, _)) = do 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 else unEscapeString source source'' <- stringToLaTeX URLString source' inHeading <- gets stInHeading return $ - (if inHeading then "\\protect\\includegraphics" else "\\includegraphics") - <> braces (text source'') + (if inHeading then "\\protect\\includegraphics" else "\\includegraphics") <> + dims <> braces (text source'') inlineToLaTeX (Note contents) = do inMinipage <- gets stInMinipage modify (\s -> s{stInNote = True}) diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index f91367eb9..5a49428f6 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -350,7 +350,7 @@ inlineToMan opts (Link txt (src, _)) = do | escapeURI s == srcSuffix -> char '<' <> text srcSuffix <> char '>' _ -> linktext <> text " (" <> text src <> char ')' -inlineToMan opts (Image alternate (source, tit)) = do +inlineToMan opts (Image _ alternate (source, tit)) = do let txt = if (null alternate) || (alternate == [Str ""]) || (alternate == [Str source]) -- to prevent autolinks then [Str "image"] diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 804f4101d..f809e5d19 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -325,8 +325,8 @@ blockToMarkdown opts (Plain inlines) = do else contents return $ contents' <> cr -- title beginning with fig: indicates figure -blockToMarkdown opts (Para [Image alt (src,'f':'i':'g':':':tit)]) = - blockToMarkdown opts (Para [Image alt (src,tit)]) +blockToMarkdown opts (Para [Image attr alt (src,'f':'i':'g':':':tit)]) = + blockToMarkdown opts (Para [Image attr alt (src,tit)]) blockToMarkdown opts (Para inlines) = (<> blankline) `fmap` blockToMarkdown opts (Plain inlines) blockToMarkdown opts (RawBlock f str) @@ -916,7 +916,7 @@ inlineToMarkdown opts (Link txt (src, tit)) = do then linktext else "[" <> linktext <> "](" <> text src <> linktitle <> ")" -inlineToMarkdown opts (Image alternate (source, tit)) = do +inlineToMarkdown opts (Image attr alternate (source, tit)) = do plain <- gets stPlain let txt = if null alternate || alternate == [Str source] -- to prevent autolinks @@ -925,7 +925,11 @@ inlineToMarkdown opts (Image alternate (source, tit)) = do linkPart <- inlineToMarkdown opts (Link txt (source, tit)) return $ if plain then "[" <> linkPart <> "]" - else "!" <> linkPart + else "!" <> linkPart <> + if isEnabled Ext_common_link_attributes opts + && attr /= nullAttr + then attrsToMarkdown attr + else empty inlineToMarkdown opts (Note contents) = do modify (\st -> st{ stNotes = contents : stNotes st }) st <- get diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 2b7c47e24..5c51157ea 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -35,6 +35,7 @@ import Text.Pandoc.Options import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared import Text.Pandoc.Pretty (render) +import Text.Pandoc.ImageSize import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.XML ( escapeStringForXML ) import Data.List ( intersect, intercalate ) @@ -44,6 +45,7 @@ import Control.Monad.State data WriterState = WriterState { stNotes :: Bool -- True if there are notes + , stOptions :: WriterOptions -- writer options } data WriterReader = WriterReader { @@ -57,7 +59,7 @@ type MediaWikiWriter = ReaderT WriterReader (State WriterState) -- | Convert Pandoc to MediaWiki. writeMediaWiki :: WriterOptions -> Pandoc -> String writeMediaWiki opts document = - let initialState = WriterState { stNotes = False } + let initialState = WriterState { stNotes = False, stOptions = opts } env = WriterReader { options = opts, listLevel = [], useTags = False } in evalState (runReaderT (pandocToMediaWiki document) env) initialState @@ -100,14 +102,15 @@ blockToMediaWiki (Plain inlines) = inlineListToMediaWiki inlines -- 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 then return "" else ("|caption " ++) `fmap` inlineListToMediaWiki txt + img <- imageToMediaWiki attr let opt = if null txt then "" 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 tags <- asks useTags @@ -312,6 +315,23 @@ alignmentToString alignment = case alignment of AlignCenter -> "center" 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. blockListToMediaWiki :: [Block] -- ^ List of block elements -> MediaWikiWriter String @@ -390,14 +410,15 @@ inlineToMediaWiki (Link txt (src, _)) = do '/':xs -> xs -- with leading / it's a _ -> 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 let txt = if null tit then if null alt then "" else '|' : alt' else '|' : tit - return $ "[[File:" ++ source ++ txt ++ "]]" + return $ "[[File:" ++ source ++ img ++ txt ++ "]]" inlineToMediaWiki (Note contents) = do contents' <- blockListToMediaWiki contents diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index b87a391fb..f7df74246 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -41,7 +41,7 @@ import Control.Applicative ((<$>)) import Text.Pandoc.Options ( WriterOptions(..) ) import Text.Pandoc.Shared ( stringify, fetchItem', warn, getDefaultReferenceODT ) -import Text.Pandoc.ImageSize ( imageSize, sizeInPoints ) +import Text.Pandoc.ImageSize ( imageSize, desiredSizeInPoints ) import Text.Pandoc.MIME ( getMimeType, extensionFromMimeType ) import Text.Pandoc.Definition import Text.Pandoc.Walk @@ -127,7 +127,7 @@ writeODT opts doc@(Pandoc meta _) = do return $ fromArchive archive'' 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 case res of Left (_ :: E.SomeException) -> do @@ -135,11 +135,12 @@ transformPicMath opts entriesRef (Image lab (src,t)) = do return $ Emph lab Right (img, mbMimeType) -> do (w,h) <- case imageSize img of - Right size -> return $ sizeInPoints size - Left msg -> do - warn $ "Could not determine image size in `" ++ - src ++ "': " ++ msg - return (0,0) + Right size -> return $ + desiredSizeInPoints opts attr size + Left msg -> do + warn $ "Could not determine image size in `" ++ + src ++ "': " ++ msg + return (0,0) let tit' = show w ++ "x" ++ show h entries <- readIORef entriesRef let extension = fromMaybe (takeExtension $ takeWhile (/='?') src) @@ -151,7 +152,7 @@ transformPicMath opts entriesRef (Image lab (src,t)) = do modifyIORef entriesRef (entry:) let fig | "fig:" `isPrefixOf` t = "fig:" | otherwise = "" - return $ Image lab (newsrc, fig++tit') + return $ Image attr lab (newsrc, fig++tit') transformPicMath _ entriesRef (Math t math) = do entries <- readIORef entriesRef let dt = if t == InlineMath then DisplayInline else DisplayBlock diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 83e17c943..1935a630f 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -288,8 +288,8 @@ blockToOpenDocument o bs | Plain b <- bs = if null b then return empty else inParagraphTags =<< inlinesToOpenDocument o b - | Para [Image c (s,'f':'i':'g':':':t)] <- bs - = figure c s t + | Para [Image attr c (s,'f':'i':'g':':':t)] <- bs + = figure attr c s t | Para b <- bs = if null b then return empty else inParagraphTags =<< inlinesToOpenDocument o b @@ -344,10 +344,10 @@ blockToOpenDocument o bs return $ inTags True "table:table" [ ("table:name" , name) , ("table:style-name", name) ] (vcat columns $$ th $$ vcat tr) $$ captionDoc - figure caption source title | null caption = - withParagraphStyle o "Figure" [Para [Image caption (source,title)]] + figure attr caption source title | null caption = + withParagraphStyle o "Figure" [Para [Image attr caption (source,title)]] | 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] return $ imageDoc $$ captionDoc @@ -394,7 +394,7 @@ inlineToOpenDocument o ils then return $ text s else return empty | 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 | otherwise = return empty where @@ -403,7 +403,7 @@ inlineToOpenDocument o ils , ("xlink:href" , s ) , ("office:name", t ) ] . inSpanTags "Definition" - mkImg s t = do + mkImg _ s t = do id' <- gets stImageId modify (\st -> st{ stImageId = id' + 1 }) return $ inTags False "draw:frame" diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 90b396cae..ffd271810 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -117,12 +117,12 @@ blockToOrg (Div attrs bs) = do nest 2 endTag $$ "#+END_HTML" $$ blankline blockToOrg (Plain inlines) = inlineListToOrg inlines -- 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 then return empty else (\c -> "#+CAPTION: " <> c <> blankline) `fmap` inlineListToOrg txt - img <- inlineToOrg (Image txt (src,tit)) + img <- inlineToOrg (Image attr txt (src,tit)) return $ capt <> img blockToOrg (Para inlines) = do contents <- inlineListToOrg inlines @@ -284,7 +284,7 @@ inlineToOrg (Link txt (src, _)) = do _ -> do contents <- inlineListToOrg txt modify $ \s -> s{ stLinks = True } return $ "[[" <> text src <> "][" <> contents <> "]]" -inlineToOrg (Image _ (source, _)) = do +inlineToOrg (Image _ _ (source, _)) = do modify $ \s -> s{ stImages = True } return $ "[[" <> text source <> "]]" inlineToOrg (Note contents) = do diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 151d3c2ae..4b68984d0 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -35,6 +35,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared +import Text.Pandoc.ImageSize import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Builder (deleteMeta) import Data.Maybe (fromMaybe) @@ -50,7 +51,7 @@ type Refs = [([Inline], Target)] data WriterState = WriterState { stNotes :: [[Block]] , stLinks :: Refs - , stImages :: [([Inline], (String, String, Maybe String))] + , stImages :: [([Inline], (Attr, String, String, Maybe String))] , stHasMath :: Bool , stHasRawTeX :: Bool , stOptions :: WriterOptions @@ -136,17 +137,22 @@ noteToRST num note = do return $ nowrap $ marker $$ nest 3 contents -- | Return RST representation of picture reference table. -pictRefsToRST :: [([Inline], (String, String, Maybe String))] +pictRefsToRST :: [([Inline], (Attr, String, String, Maybe String))] -> State WriterState Doc pictRefsToRST refs = mapM pictToRST refs >>= return . vcat -- | Return RST representation of a picture substitution reference. -pictToRST :: ([Inline], (String, String,Maybe String)) +pictToRST :: ([Inline], (Attr, String, String, Maybe String)) -> State WriterState Doc -pictToRST (label, (src, _, mbtarget)) = do +pictToRST (label, (attr, src, _, mbtarget)) = do label' <- inlineListToRST label + dims <- imageDimsToRST attr + let (_, cls, _) = attr + classes = if null cls + then empty + else ":class: " <> text (unwords cls) return $ nowrap - $ ".. |" <> label' <> "| image:: " <> text src + $ ".. |" <> label' <> "| image:: " <> text src $$ hang 3 empty (classes $$ dims) $$ case mbtarget of Nothing -> empty Just t -> " :target: " <> text t @@ -181,11 +187,16 @@ blockToRST (Div attr bs) = do return $ blankline <> startTag $+$ contents $+$ endTag $$ blankline blockToRST (Plain inlines) = inlineListToRST inlines -- 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 + dims <- imageDimsToRST attr let fig = "figure:: " <> text src - let alt = ":alt: " <> if null tit then capt else text tit - return $ hang 3 ".. " (fig $$ alt $+$ capt) $$ blankline + alt = ":alt: " <> if null tit then capt else text tit + (_,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) | LineBreak `elem` inlines = do -- use line block if LineBreaks lns <- mapM inlineListToRST $ splitBy (==LineBreak) inlines @@ -380,7 +391,7 @@ inlineListToRST lst = isComplex (Superscript _) = True isComplex (Subscript _) = True isComplex (Link _ _) = True - isComplex (Image _ _) = True + isComplex (Image _ _ _) = True isComplex (Code _ _) = True isComplex (Math _ _) = True isComplex _ = False @@ -438,8 +449,8 @@ inlineToRST (Link [Str str] (src, _)) else src == escapeURI str = do let srcSuffix = fromMaybe src (stripPrefix "mailto:" src) return $ text srcSuffix -inlineToRST (Link [Image alt (imgsrc,imgtit)] (src, _tit)) = do - label <- registerImage alt (imgsrc,imgtit) (Just src) +inlineToRST (Link [Image attr alt (imgsrc,imgtit)] (src, _tit)) = do + label <- registerImage attr alt (imgsrc,imgtit) (Just src) return $ "|" <> label <> "|" inlineToRST (Link txt (src, tit)) = do useReferenceLinks <- get >>= return . writerReferenceLinks . stOptions @@ -456,8 +467,8 @@ inlineToRST (Link txt (src, tit)) = do modify $ \st -> st { stLinks = (txt,(src,tit)):refs } return $ "`" <> linktext <> "`_" else return $ "`" <> linktext <> " <" <> text src <> ">`__" -inlineToRST (Image alternate (source, tit)) = do - label <- registerImage alternate (source,tit) Nothing +inlineToRST (Image attr alternate (source, tit)) = do + label <- registerImage attr alternate (source,tit) Nothing return $ "|" <> label <> "|" inlineToRST (Note contents) = do -- add to notes in state @@ -466,16 +477,33 @@ inlineToRST (Note contents) = do let ref = show $ (length notes) + 1 return $ " [" <> text ref <> "]_" -registerImage :: [Inline] -> Target -> Maybe String -> State WriterState Doc -registerImage alt (src,tit) mbtarget = do +registerImage :: Attr -> [Inline] -> Target -> Maybe String -> State WriterState Doc +registerImage attr alt (src,tit) mbtarget = do pics <- get >>= return . stImages 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 let alt' = if null alt || alt == [Str ""] then [Str $ "image" ++ show (length pics)] else alt modify $ \st -> st { stImages = - (alt', (src,tit, mbtarget)):stImages st } + (alt', (attr,src,tit, mbtarget)):stImages st } return alt' 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 diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index 9eb02ad02..c89e88fad 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -46,7 +46,7 @@ import Text.Pandoc.ImageSize -- or a MediaBag, or the internet. -- If file not found or filetype not jpeg or png, leave the inline unchanged. 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 case result of Right (imgdata, Just mime) @@ -63,12 +63,12 @@ rtfEmbedImage opts x@(Image _ (src,_)) = do return "" Right sz -> return $ "\\picw" ++ show xpx ++ "\\pich" ++ show ypx ++ - "\\picwgoal" ++ show (xpt * 20) - ++ "\\pichgoal" ++ show (ypt * 20) + "\\picwgoal" ++ show (floor (xpt * 20) :: Integer) + ++ "\\pichgoal" ++ show (floor (ypt * 20) :: Integer) -- twip = 1/1440in = 1/20pt where (xpx, ypx) = sizeInPixels sz - (xpt, ypt) = sizeInPoints sz - let raw = "{\\pict" ++ filetype ++ sizeSpec ++ " " ++ + (xpt, ypt) = desiredSizeInPoints opts attr sz + let raw = "{\\pict" ++ filetype ++ sizeSpec ++ "\\bin " ++ concat bytes ++ "}" return $ if B.null imgdata then x @@ -353,7 +353,7 @@ inlineToRTF Space = " " inlineToRTF (Link text (src, _)) = "{\\field{\\*\\fldinst{HYPERLINK \"" ++ (codeStringToRTF src) ++ "\"}}{\\fldrslt{\\ul\n" ++ (inlineListToRTF text) ++ "\n}}}\n" -inlineToRTF (Image _ (source, _)) = +inlineToRTF (Image _ _ (source, _)) = "{\\cf1 [image: " ++ source ++ "]\\cf0}" inlineToRTF (Note contents) = "{\\super\\chftn}{\\*\\footnote\\chftn\\~\\plain\\pard " ++ diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 2325d1425..a8e1e15a6 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -40,6 +40,7 @@ import Data.Ord ( comparing ) import Data.Char ( chr, ord ) import Control.Monad.State import Text.Pandoc.Pretty +import Text.Pandoc.ImageSize import Network.URI ( isURI, unEscapeString ) import System.FilePath @@ -49,6 +50,7 @@ data WriterState = , stSubscript :: Bool -- document contains subscript , stEscapeComma :: Bool -- in a context where we need @comma , stIdentifiers :: [String] -- header ids used already + , stOptions :: WriterOptions -- writer options } {- TODO: @@ -61,7 +63,8 @@ writeTexinfo :: WriterOptions -> Pandoc -> String writeTexinfo options document = evalState (pandocToTexinfo options $ wrapTop document) $ 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. wrapTop :: Pandoc -> Pandoc @@ -130,12 +133,12 @@ blockToTexinfo (Plain lst) = inlineListToTexinfo lst -- 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 then return empty else (\c -> text "@caption" <> braces c) `fmap` inlineListToTexinfo txt - img <- inlineToTexinfo (Image txt (src,tit)) + img <- inlineToTexinfo (Image attr txt (src,tit)) return $ text "@float" $$ img $$ capt $$ text "@end float" blockToTexinfo (Para lst) = @@ -437,10 +440,16 @@ inlineToTexinfo (Link txt (src, _)) = do return $ text ("@uref{" ++ src1 ++ ",") <> contents <> char '}' -inlineToTexinfo (Image alternate (source, _)) = do +inlineToTexinfo (Image attr alternate (source, _)) = do content <- escapeCommas $ inlineListToTexinfo alternate - return $ text ("@image{" ++ base ++ ",,,") <> content <> text "," <> - text (ext ++ "}") + opts <- gets stOptions + 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 ext = drop 1 $ takeExtension source' base = dropExtension source' diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 126c1e62e..dde9a7177 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -34,6 +34,7 @@ import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.Shared import Text.Pandoc.Pretty (render) +import Text.Pandoc.ImageSize import Text.Pandoc.Writers.Shared import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.XML ( escapeStringForXML ) @@ -115,9 +116,9 @@ blockToTextile opts (Plain inlines) = inlineListToTextile opts inlines -- 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) - im <- inlineToTextile opts (Image txt (src,tit)) + im <- inlineToTextile opts (Image attr txt (src,tit)) return $ im ++ "\n" ++ capt blockToTextile opts (Para inlines) = do @@ -434,14 +435,28 @@ inlineToTextile opts (Link txt (src, _)) = do _ -> inlineListToTextile opts txt return $ "\"" ++ label ++ "\":" ++ src -inlineToTextile opts (Image alt (source, tit)) = do +inlineToTextile opts (Image attr alt (source, tit)) = do alt' <- inlineListToTextile opts alt let txt = if null tit then if null alt' then "" else "(" ++ alt' ++ ")" else "(" ++ tit ++ ")" - return $ "!" ++ source ++ txt ++ "!" + (_, cls, _) = attr + 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 curNotes <- liftM stNotes get From 564b0c43b064fc235eb3b2ac83e8c0812d825011 Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Thu, 2 Apr 2015 21:09:22 -0700 Subject: [PATCH 10/14] Updated Arbitrary instance for new image attribute parameter. --- tests/Tests/Arbitrary.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/tests/Tests/Arbitrary.hs b/tests/Tests/Arbitrary.hs index 3675d97bf..de07322fb 100644 --- a/tests/Tests/Arbitrary.hs +++ b/tests/Tests/Arbitrary.hs @@ -60,10 +60,11 @@ arbInline n = frequency $ [ (60, liftM Str realString) x3 <- realString x2 <- liftM escapeURI realString return $ Link x1 (x2,x3)) - , (10, do x1 <- arbInlines (n-1) + , (10, do x0 <- arbAttr + x1 <- arbInlines (n-1) x3 <- realString x2 <- liftM escapeURI realString - return $ Image x1 (x2,x3)) + return $ Image x0 x1 (x2,x3)) , (2, liftM2 Cite arbitrary (arbInlines 1)) , (2, liftM Note $ resize 3 $ listOf1 $ arbBlock (n-1)) ] From e44fc547a5d0ef67c68011c23563fd82320bc2aa Mon Sep 17 00:00:00 2001 From: John MacFarlane Date: Wed, 1 Apr 2015 17:03:00 -0700 Subject: [PATCH 11/14] Updated tests for image attribute changes. --- tests/docbook-reader.native | 6 ++--- tests/docx/image_no_embed.native | 2 +- tests/docx/image_no_embed_writer.native | 2 +- tests/docx/image_vml.native | 2 +- tests/docx/inline_images.native | 4 ++-- tests/docx/inline_images_writer.native | 4 ++-- tests/dokuwiki_external_images.native | 2 +- tests/dokuwiki_multiblock_table.native | 2 +- tests/epub/wasteland.native | 2 +- tests/html-reader.native | 4 ++-- tests/latex-reader.latex | 27 ---------------------- tests/latex-reader.native | 15 +++---------- tests/mediawiki-reader.native | 12 +++++----- tests/mediawiki-reader.wiki | 4 ++++ tests/rst-reader.native | 8 +++---- tests/tables.icml | 2 +- tests/testsuite.native | 4 ++-- tests/textile-reader.native | 2 +- tests/txt2tags.native | 18 +++++++-------- tests/writer.icml | 30 ++++++++++++------------- tests/writer.native | 4 ++-- tests/writer.rtf | 4 ++-- 22 files changed, 64 insertions(+), 96 deletions(-) diff --git a/tests/docbook-reader.native b/tests/docbook-reader.native index b87e28d1c..5e76bdc0b 100644 --- a/tests/docbook-reader.native +++ b/tests/docbook-reader.native @@ -270,9 +270,9 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,CodeBlock ("",[],[]) "or here: " ,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 [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 [Image [Str "lalune",Space,Str "no",Space,Str "figure",Space,Str "alt",Space,Str "text"] ("lalune.jpg","")] +,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 [Image ("",[],[]) [Str "lalune",Space,Str "no",Space,Str "figure",Space,Str "alt",Space,Str "text"] ("lalune.jpg","")] ,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 ("",[],[]) " { }",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 diff --git a/tests/docx/image_no_embed.native b/tests/docx/image_no_embed.native index 95c73610e..9af018a0d 100644 --- a/tests/docx/image_no_embed.native +++ b/tests/docx/image_no_embed.native @@ -1,2 +1,2 @@ [Para [Str "An",Space,Str "image:"] -,Para [Image [] ("media/image1.jpg","")]] +,Para [Image ("",[],[]) [] ("media/image1.jpg","")]] diff --git a/tests/docx/image_no_embed_writer.native b/tests/docx/image_no_embed_writer.native index 21802ebd1..fb0f4f0a1 100644 --- a/tests/docx/image_no_embed_writer.native +++ b/tests/docx/image_no_embed_writer.native @@ -1,2 +1,2 @@ [Para [Str "An",Space,Str "image:"] -,Para [Image [] ("media/rId25.jpg","")]] +,Para [Image ("",[],[]) [] ("media/rId25.jpg","")]] diff --git a/tests/docx/image_vml.native b/tests/docx/image_vml.native index 8c5450a19..e9fded614 100644 --- a/tests/docx/image_vml.native +++ b/tests/docx/image_vml.native @@ -1,4 +1,4 @@ [Header 1 ("vml-image",[],[]) [Strong [Str "VML",Space,Str "Image"]] ,BlockQuote [Para [Str "It",Space,Str "should",Space,Str "follow",Space,Str "below:"] - ,Para [Image [] ("media/image4.jpeg","")]]] + ,Para [Image ("",[],[]) [] ("media/image4.jpeg","")]]] diff --git a/tests/docx/inline_images.native b/tests/docx/inline_images.native index f962f5c09..ac6e33fc1 100644 --- a/tests/docx/inline_images.native +++ b/tests/docx/inline_images.native @@ -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 "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 "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."]] diff --git a/tests/docx/inline_images_writer.native b/tests/docx/inline_images_writer.native index da2a2709b..a0b63fece 100644 --- a/tests/docx/inline_images_writer.native +++ b/tests/docx/inline_images_writer.native @@ -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 "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 "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."]] diff --git a/tests/dokuwiki_external_images.native b/tests/dokuwiki_external_images.native index c2b8876d3..0f103461e 100644 --- a/tests/dokuwiki_external_images.native +++ b/tests/dokuwiki_external_images.native @@ -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","")]] diff --git a/tests/dokuwiki_multiblock_table.native b/tests/dokuwiki_multiblock_table.native index ea6b833db..34824296d 100644 --- a/tests/dokuwiki_multiblock_table.native +++ b/tests/dokuwiki_multiblock_table.native @@ -10,4 +10,4 @@ ,[Para [Str "$2.10"]] ,[BulletList [[Plain [Str "cures",Space,Str "scurvy"]] - ,[Plain [Str "tasty"]]]]]]] \ No newline at end of file + ,[Plain [Str "tasty"]]]]]]] diff --git a/tests/epub/wasteland.native b/tests/epub/wasteland.native index 96418226e..d931eec32 100644 --- a/tests/epub/wasteland.native +++ b/tests/epub/wasteland.native @@ -1,4 +1,4 @@ -[Para [Image [] ("wasteland-cover.jpg","")] +[Para [Image ("",[],[]) [] ("wasteland-cover.jpg","")] ,Para [Span ("wasteland-content.xhtml",[],[]) []] ,RawBlock (Format "html") "
" ,RawBlock (Format "html") "
" diff --git a/tests/html-reader.native b/tests/html-reader.native index b2d660fda..13ee9d516 100644 --- a/tests/html-reader.native +++ b/tests/html-reader.native @@ -296,8 +296,8 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl ,HorizontalRule ,Header 1 ("",[],[]) [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 [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 [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."] ,HorizontalRule ,Header 1 ("",[],[]) [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)."] diff --git a/tests/latex-reader.latex b/tests/latex-reader.latex index 4324dbfbe..2ebdfed99 100644 --- a/tests/latex-reader.latex +++ b/tests/latex-reader.latex @@ -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} diff --git a/tests/latex-reader.native b/tests/latex-reader.native index fbc191125..8f51e409f 100644 --- a/tests/latex-reader.native +++ b/tests/latex-reader.native @@ -361,8 +361,8 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,HorizontalRule ,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 [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 [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."] ,HorizontalRule ,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 ("",[],[]) " { }",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]."]]] @@ -372,13 +372,4 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa [[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."] ,Header 1 ("escaped-characters",[],[]) [Str "Escaped",Space,Str "characters"] -,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"]] +,Para [Str "$",Space,Str "%",Space,Str "&",Space,Str "#",Space,Str "_",Space,Str "{",Space,Str "}"]] diff --git a/tests/mediawiki-reader.native b/tests/mediawiki-reader.native index 2f508c32f..d03182146 100644 --- a/tests/mediawiki-reader.native +++ b/tests/mediawiki-reader.native @@ -84,11 +84,13 @@ Pandoc (Meta {unMeta = fromList []}) ,Para [Link [Str "#My",Space,Str "anchor"] ("#My_anchor","wikilink")] ,Para [Link [Str "and",Space,Str "text"] ("Page#with_anchor","wikilink")] ,Header 2 ("images",[],[]) [Str "images"] -,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 "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")] +,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 ("",[],[("width","30"),("height","40")]) [Str "caption"] ("example.jpg","fig:caption")] +,Para [Image ("",[],[("width","30")]) [Str "caption"] ("example.jpg","fig:caption")] +,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"] ,BulletList [[Plain [Str "Start",Space,Str "each",Space,Str "line"]] diff --git a/tests/mediawiki-reader.wiki b/tests/mediawiki-reader.wiki index f30dafa33..2820ed171 100644 --- a/tests/mediawiki-reader.wiki +++ b/tests/mediawiki-reader.wiki @@ -171,6 +171,10 @@ http://pandoc.org [[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]] [[Archivo:example_es.jpg]] diff --git a/tests/rst-reader.native b/tests/rst-reader.native index 1f402f835..a3b462d8b 100644 --- a/tests/rst-reader.native +++ b/tests/rst-reader.native @@ -220,10 +220,10 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,CodeBlock ("",[],[]) "http://example.com/" ,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 [Image [Str "image"] ("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 "And",Space,Str "an",Space,Link [Image [Str "A movie"] ("movie.jpg","")] ("/url",""),Str "."] +,Para [Image ("",[],[]) [Str "image"] ("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 "And",Space,Str "an",Space,Link [Image ("",[],[]) [Str "A movie"] ("movie.jpg","")] ("/url",""),Str "."] ,Header 1 ("comments",[],[]) [Str "Comments"] ,Para [Str "First",Space,Str "paragraph"] ,Para [Str "Another",Space,Str "paragraph"] diff --git a/tests/tables.icml b/tests/tables.icml index eb73af670..edb022737 100644 --- a/tests/tables.icml +++ b/tests/tables.icml @@ -745,4 +745,4 @@
-
+ \ No newline at end of file diff --git a/tests/testsuite.native b/tests/testsuite.native index 93d2939ad..760729b0c 100644 --- a/tests/testsuite.native +++ b/tests/testsuite.native @@ -389,8 +389,8 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,HorizontalRule ,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 [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 [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."] ,HorizontalRule ,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 ("",[],[]) " { }",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]."]]] diff --git a/tests/textile-reader.native b/tests/textile-reader.native index de0637f5f..18198ed60 100644 --- a/tests/textile-reader.native +++ b/tests/textile-reader.native @@ -130,7 +130,7 @@ Pandoc (Meta {unMeta = fromList []}) ,[Plain [Str "45"]] ,[Plain [Str "f"]]]] ,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 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"]] diff --git a/tests/txt2tags.native b/tests/txt2tags.native index 189c099e2..382829e91 100644 --- a/tests/txt2tags.native +++ b/tests/txt2tags.native @@ -36,15 +36,15 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]] ,Header 1 ("link",[],[]) [Str "Link"] ,Para [Link [Str "mailto:user@domain.com"] ("user@domain.com",""),Space,Link [Str "mailto:user@domain.com"] ("user@domain.com",""),Str ".",Space,Link [Str "mailto:user@domain.com"] ("user@domain.com",""),Str ".",Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "mailto:user@domain.com"] ("user@domain.com",""),Str ".",Space,Str "any",Space,Str "text.",Space,Link [Str "label"] ("user@domain.com",""),Space,Link [Str "mailto:user@domain.com?subject=bla"] ("user@domain.com?subject=bla",""),Space,Link [Str "mailto:user@domain.com?subject=bla"] ("user@domain.com?subject=bla",""),Str ".",Space,Link [Str "mailto:user@domain.com?subject=bla"] ("user@domain.com?subject=bla",""),Str ",",Space,Link [Str "mailto:user@domain.com?subject=bla&cc=otheruser@domain.com"] ("user@domain.com?subject=bla&cc=otheruser@domain.com",""),Space,Link [Str "mailto:user@domain.com?subject=bla&cc=otheruser@domain.com"] ("user@domain.com?subject=bla&cc=otheruser@domain.com",""),Str ".",Space,Link [Str "mailto:user@domain.com?subject=bla&cc=otheruser@domain.com"] ("user@domain.com?subject=bla&cc=otheruser@domain.com",""),Str ",",Space,Link [Str "label"] ("user@domain.com?subject=bla&cc=otheruser@domain.com",""),Str ".",Space,Link [Str "label"] ("user@domain.com?subject=bla&cc=otheruser@domain.com.",""),Str ".",Space,Link [Str "http://www.domain.com"] ("http://www.domain.com",""),Space,Link [Str "http://www.domain.com/dir/"] ("http://www.domain.com/dir/",""),Space,Link [Str "http://www.domain.com/dir///"] ("http://www.domain.com/dir///",""),Space,Link [Str "http://www.domain.com."] ("http://www.domain.com.",""),Space,Link [Str "http://www.domain.com,"] ("http://www.domain.com,",""),Space,Link [Str "http://www.domain.com."] ("http://www.domain.com.",""),Space,Str "any",Space,Str "text.",Space,Link [Str "http://www.domain.com,"] ("http://www.domain.com,",""),Space,Str "any",Space,Str "text.",Space,Link [Str "http://www.domain.com/dir/."] ("http://www.domain.com/dir/.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "http://www.domain.com."] ("http://www.domain.com.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "http://www.domain.com/dir/."] ("http://www.domain.com/dir/.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "http://www.domain.com/dir/index.html."] ("http://www.domain.com/dir/index.html.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "http://www.domain.com/dir/index.html,"] ("http://www.domain.com/dir/index.html,",""),Space,Str "any",Space,Str "text.",Space,Link [Str "http://www.domain.com/dir/#anchor"] ("http://www.domain.com/dir/#anchor",""),Space,Link [Str "http://www.domain.com/dir/index.html#anchor"] ("http://www.domain.com/dir/index.html#anchor",""),Space,Link [Str "http://www.domain.com/dir/index.html#anchor."] ("http://www.domain.com/dir/index.html#anchor.",""),Space,Link [Str "http://www.domain.com/dir/#anchor."] ("http://www.domain.com/dir/#anchor.",""),Space,Str "any",Space,Str "text.",Space,Link [Str "http://www.domain.com/dir/index.html#anchor."] ("http://www.domain.com/dir/index.html#anchor.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "http://www.domain.com/dir/#anchor."] ("http://www.domain.com/dir/#anchor.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "http://www.domain.com/dir/index.html#anchor."] ("http://www.domain.com/dir/index.html#anchor.",""),Space,Str "any",Space,Str "text.",Space,Link [Str "http://domain.com?a=a@a.a&b=a+b+c."] ("http://domain.com?a=a@a.a&b=a+b+c.",""),Space,Link [Str "http://domain.com?a=a@a.a&b=a+b+c,"] ("http://domain.com?a=a@a.a&b=a+b+c,",""),Space,Link [Str "http://domain.com/bla.cgi?a=a@a.a&b=a+b+c."] ("http://domain.com/bla.cgi?a=a@a.a&b=a+b+c.",""),Space,Link [Str "http://domain.com/bla.cgi?a=a@a.a&b=a+b+c@."] ("http://domain.com/bla.cgi?a=a@a.a&b=a+b+c@.",""),Space,Link [Str "http://domain.com?a=a@a.a&b=a+b+c.#anchor"] ("http://domain.com?a=a@a.a&b=a+b+c.#anchor",""),Space,Link [Str "http://domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor"] ("http://domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor",""),Space,Link [Str "http://domain.com/bla.cgi?a=a@a.a&b=a+b+c@.#anchor"] ("http://domain.com/bla.cgi?a=a@a.a&b=a+b+c@.#anchor",""),Space,Link [Str "http://user:password@domain.com/bla.html."] ("http://user:password@domain.com/bla.html.",""),Space,Link [Str "http://user:password@domain.com/dir/."] ("http://user:password@domain.com/dir/.",""),Space,Link [Str "http://user:password@domain.com."] ("http://user:password@domain.com.",""),Space,Link [Str "http://user:@domain.com."] ("http://user:@domain.com.",""),Space,Link [Str "http://user@domain.com."] ("http://user@domain.com.",""),Space,Link [Str "http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor"] ("http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor",""),Space,Link [Str "http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c@#anchor"] ("http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c@#anchor",""),Space,Link [Str "label"] ("www.domain.com",""),Space,Str "[",Space,Str "label",Space,Link [Str "www.domain.com"] ("www.domain.com",""),Str "]",Space,Link [Str "label",Space] ("www.domain.com",""),Space,Link [Str "anchor",Space] ("http://www.domain.com/dir/index.html#anchor.",""),Space,Link [Str "login",Space] ("http://user:password@domain.com/bla.html",""),Space,Link [Str "form",Space] ("http://www.domain.com/bla.cgi?a=a@a.a&b=a+b+c.",""),Space,Link [Str "form",Space,Str "&",Space,Str "anchor"] ("http://www.domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor",""),Space,Link [Str "login",Space,Str "&",Space,Str "form",Space] ("http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c.",""),Space,Link [Str "local",Space,Str "link",Space,Str "up",Space] ("..",""),Space,Link [Str "local",Space,Str "link",Space,Str "file",Space] ("bla.html",""),Space,Link [Str "local",Space,Str "link",Space,Str "anchor",Space] ("#anchor",""),Space,Link [Str "local",Space,Str "link",Space,Str "file/anchor"] ("bla.html#anchor",""),Space,Link [Str "local",Space,Str "link",Space,Str "file/anchor"] ("bla.html#anchor.",""),Space,Link [Str "local",Space,Str "link",Space,Str "img",Space] ("abc.gif",""),Space,Link [Str "www.fake.com"] ("www.domain.com",""),Space,Link [Str "http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm"] ("http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm",""),Space,Link [Str "http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-"] ("http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-",""),Space,Link [Str "http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_"] ("http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_",""),Str "-1%.",Space,Link [Str "http://foo._user-9:pass!#$%&*()+word@domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_"] ("http://foo._user-9:pass!#$%&*()+word@domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_",""),Str "-1%.",Space,Link [Str "http://L1.com"] ("http://L1.com",""),Space,Str "!",Space,Link [Str "mailto:L2@www.com"] ("L2@www.com",""),Space,Str "!",Space,Link [Str "L3"] ("www.com",""),Space,Str "!",Space,Link [Str "L4"] ("w@ww.com",""),Space,Str "!",Space,Link [Str "www.L5.com"] ("www.L5.com",""),Space,Link [Str "www.domain.com"] ("www.domain.com",""),Space,Link [Str "www2.domain.com"] ("www2.domain.com",""),Space,Link [Str "ftp.domain.com"] ("ftp.domain.com",""),Space,Link [Str "WWW.DOMAIN.COM"] ("WWW.DOMAIN.COM",""),Space,Link [Str "FTP.DOMAIN.COM"] ("FTP.DOMAIN.COM",""),Space,Link [Str "label"] ("www.domain.com",""),Space,Link [Str "label"] ("ftp.domain.com",""),Space,Link [Str "label"] ("WWW.DOMAIN.COM",""),Space,Link [Str "label"] ("FTP.DOMAIN.COM",""),Space,Str "[label",Space,Link [Str "www.domain.com"] ("www.domain.com",""),Space,Str "]",Space,Str "[label]",Space,Link [Str "www.domain.com"] ("www.domain.com",""),Str "]"] ,Header 1 ("image",[],[]) [Str "Image"] -,Para [Image [] ("img.png","")] -,Para [Link [Image [] ("img.png","")] ("http://txt2tags.org","")] -,Para [Image [] ("img.png",""),Space,Str "Image",Space,Str "at",Space,Str "the",Space,Str "line",Space,Str "beginning."] -,Para [Str "Image",Space,Str "in",Space,Str "the",Space,Str "middle",Space,Image [] ("img.png",""),Space,Str "of",Space,Str "the",Space,Str "line."] -,Para [Str "Image",Space,Str "at",Space,Str "the",Space,Str "line",Space,Str "end.",Space,Image [] ("img.png","")] -,Para [Image [] ("img.png",""),Space,Image [] ("img.png",""),Space,Image [] ("img.png","")] -,Para [Image [] ("img.png",""),Image [] ("img.png","")] -,Para [Str "Images",Space,Image [] ("img.png",""),Space,Str "mixed",Space,Image [] ("img.png",""),Space,Str "with",Space,Image [] ("img.png",""),Space,Str "text."] -,Para [Str "Images",Space,Str "glued",Space,Str "together:",Space,Image [] ("img.png",""),Image [] ("img.png",""),Image [] ("img.png",""),Str "."] +,Para [Image ("",[],[]) [] ("img.png","")] +,Para [Link [Image ("",[],[]) [] ("img.png","")] ("http://txt2tags.org","")] +,Para [Image ("",[],[]) [] ("img.png",""),Space,Str "Image",Space,Str "at",Space,Str "the",Space,Str "line",Space,Str "beginning."] +,Para [Str "Image",Space,Str "in",Space,Str "the",Space,Str "middle",Space,Image ("",[],[]) [] ("img.png",""),Space,Str "of",Space,Str "the",Space,Str "line."] +,Para [Str "Image",Space,Str "at",Space,Str "the",Space,Str "line",Space,Str "end.",Space,Image ("",[],[]) [] ("img.png","")] +,Para [Image ("",[],[]) [] ("img.png",""),Space,Image ("",[],[]) [] ("img.png",""),Space,Image ("",[],[]) [] ("img.png","")] +,Para [Image ("",[],[]) [] ("img.png",""),Image ("",[],[]) [] ("img.png","")] +,Para [Str "Images",Space,Image ("",[],[]) [] ("img.png",""),Space,Str "mixed",Space,Image ("",[],[]) [] ("img.png",""),Space,Str "with",Space,Image ("",[],[]) [] ("img.png",""),Space,Str "text."] +,Para [Str "Images",Space,Str "glued",Space,Str "together:",Space,Image ("",[],[]) [] ("img.png",""),Image ("",[],[]) [] ("img.png",""),Image ("",[],[]) [] ("img.png",""),Str "."] ,Para [Str "[img.png",Space,Str "]"] ,Para [Str "[",Space,Str "img.png]"] ,Para [Str "[",Space,Str "img.png",Space,Str "]"] diff --git a/tests/writer.icml b/tests/writer.icml index b6f5b5e32..c00d485bc 100644 --- a/tests/writer.icml +++ b/tests/writer.icml @@ -2494,27 +2494,26 @@ These should not be escaped: \$ \\ \> \[ \{ - + - - - - + + + + - + $ID/Embedded - - +
@@ -2524,27 +2523,26 @@ These should not be escaped: \$ \\ \> \[ \{ Here is a movie - + - - - - + + + + - + $ID/Embedded - - + diff --git a/tests/writer.native b/tests/writer.native index 93d2939ad..760729b0c 100644 --- a/tests/writer.native +++ b/tests/writer.native @@ -389,8 +389,8 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,HorizontalRule ,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 [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 [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."] ,HorizontalRule ,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 ("",[],[]) " { }",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]."]]] diff --git a/tests/writer.rtf b/tests/writer.rtf index 08d3c1fee..a79ae6fb5 100644 --- a/tests/writer.rtf +++ b/tests/writer.rtf @@ -429,8 +429,8 @@ http://example.com/ {\pard \qc \f0 \sa180 \li0 \fi0 \emdash\emdash\emdash\emdash\emdash\par} {\pard \ql \f0 \sa180 \li0 \fi0 \b \fs36 Images\par} {\pard \ql \f0 \sa180 \li0 \fi0 From \u8220"Voyage dans la Lune\u8221" by Georges Melies (1902):\par} -{\pard \ql \f0 \sa180 \li0 \fi0 {\pict\jpegblip\picw250\pich250\picwgoal3000\pichgoal3000 ffd8ffe000104a46494600010101007800780000ffdb00430006040506050406060506070706080a100a0a09090a140e0f0c1017141818171416161a1d251f1a1b231c1616202c20232627292a29191f2d302d283025282928ffdb0043010707070a080a130a0a13281a161a2828282828282828282828282828282828282828282828282828282828282828282828282828282828282828282828282828ffc000110800fa00fa03011100021101031101ffc4001c0000000701010000000000000000000000010203040506070008ffc4003e100002010303020404040502050500030001020300041105122106311322415107617181143291a1234252b1c115f016336272d1082443e1f1265382ffc40017010101010100000000000000000000000000010204ffc4001b11010101010003010000000000000000000001110212213141ffda000c03010002110311003f00dadd18a10a704f6a95ccc57e37750782b0d8d9ea0cd32e7c5446e07e9f4ad723119a7b89e61e348f260719278aad613cbb640002938c76a182b264fc87bd13009c0c019c76e3d68a072e1cf6f4cd502d330c28269a61bb39c923923d4fad44c08dccb95cfd28b8280769ee08a263891e1808739e4f1d8d149392172cc714050dbb9fde8960ed8c60b79b1ed44103b05c331dbdb1dc5026ac1946d20ff8140aa631c773ec738a0346a003bf93e9cf02801895e7b9a01886796c923bd0090a06393c76a0142003ce3d86680d8dd9392303f5341ccc1b3cf7a2c812c37e4923d381429757013209fa511c18146c9247a0f6a007900c0c671c6280854e086c673eb45c27c038fd68aedff2fda836ef881f136f25d5e6b7d1262964aa02b03f98fbf153131935edcc97576f35c33349212cc4f39f7ab26186dfce5b200f73451f7600dcb8cf27e7400c0b291914046c9e0718fde81371b8e7273f4ef4007691919240e714097f31f376e7b5008caee27807b0f5a02c8e1b3c6d27d33cd0201d839523144d1a149ae084b78da47638211771fd050d582c3a0faab5119b6d12f8ab1c06788a0fd4e2ac356fd1fe08754ddccaba849696309e598c9e2103fed1dcfdeadc44fea5ff00a7f956366d375e492403ca935bedcf1eea4ff6ac68a55efc1beb3b552574f8e7009ff933a927ec715bc82b3a8f4d6bba5ca1352d22fe061cf9a0383f71dea5119cc6c0baed3eaac0f1fad40897dcc3d81f7a052366c1007df3400f21edefc5008c28f30c9c5170ee4fc37830086395250a7c66770c18e78da31c0c63de8609b41f7c515c5172a30c3b76344a3e377cb2339cf7a242aea89808cce368272b8c1a2e107c672a49f5c1a181c9c7ae7da8a2119e7b1f5068099ffa68258a132062d8f9e0f34059502b61bf2824e681bb297ced2a71efda80f19c47b9c77fdbe74057c13e539cf3c1a0eeeb9c73f33405ddb4f18249c1e28062b79ae242902024465b9214614649e7bd0362a7249eddc513456e5720f38f5a1a98e96e95d6baa6ebc2d1ad1e65521649bb469f563534d6d7d31f04347d2a2fc5f535db6a0e83718906c887cbbe5a9a8bef44dce9f731ca9a2e89169d6d6f2184b1455dc07b11dcfeb4d16f119c649a681285b03d3e5500f87820ff006a0e098191de80ac9b8904647b55d11da9681a56a31f87a869f6970b8ffe4883629a289aefc16e92d441682da5b098f21ed9f033f353914d19b751fc08d66cc16d12fe2bf45ec92ff0df1fdbfb559ec667aff4eeb1a04db359d3ae6d40eccebe53f46ec7f5ab82263da7dcf3eb5174e5181076918c7de869503232491ee4515c1803824f03b51287f30e0e7d803449494832c157278a2e8c71fcb9f9d144639236824d01e142efb1768cfb9c7ef40512a818de78ff00a682518e7cc30ab9e00a02cce9953247bd41e467191ed9a04205ee99da4e4e3d283a524b0427b5026c18a8e082067db8341ce0e39ed409b6502907391edda80f2dfdc496f0c124ac6184b144cf0a4e338fd2894f7a7342d4ba9b568f4fd261f12571966270a8bfd47d8511bae85f02b47b7fc34bac5d5c5dc88a0c90ab6c8d9bedce3ef4d1ad691a6dae976a96d616d15b409f9638d70054a1dbc68ea51d4329f4619a8022b78e04548515117b05000a035c5c4702a995c26e3819f534047bcb68a458cce866719540724d02e41c0f7a012a40f6141cbc8e7bd01719e38e6838af1c0a04ca8206d3cd037bdb082fad9e0bd8a39e0718649141047d0d5d18f759fc0cd3af164b8e9999acae4e4f81236e898f7c0f55fed574615aee83a96817ef67abda3db4ebdb7f66f983d88a061bb8db9e3d45165076db83c1f950a53780d8247c80a2398f182724f1c7ad080c608cfa7a51a0062adc7afbd0130173bb9c5070f071cb37e82826106e8f615e01c9e680d6b35bc534be3c1e3831b2aa962bb188f2b71df1de819ae4b1048c7f57bd01a58268e332642ae0704f7cf6207af6a01b99e17b7b6416e227407c494139909ed9f4c0a04a4e501e0f1eb40d263e53dce7fa682c9d0bd13abf58dd6db18bc2b157c4975270ab8ef8f563f21447a73a03a1f4de8eb031582b497328066b97fcd21ff038edfde88b7e32703bd64188e7e6283864b73400cd804b67ca3268317eacea6d56ff005233592f8b6303f953fa4af7c2fa93417fe98b763e0ea171297bab98558068f695ce0e08fdbd281e5c6a57ba5e9d14d716ef7774f2ec112601da4f27ec2827ada74bab559a20e148fcae36b0f91140283729c77a0e0a7777a01dac68395719e39a029607cb901b19c501480ab9279f4a086ea8d0b48d76c0586b7143224a76c61ce1831fe93e86b43cd1f12fe19ea7d2533dcdbeebcd20b612651e68f9ece3fcf6fa5067cbcf20ff009a051724905411e94032799060723da8406d6c67e7ea68d0e1770fe5cfb5026c37039ef9a02eca098c91e6e01e71c500b1d8a49c12786cf6a06a4e256008e3d050119958007920e2801154e32fb4120927b014017eb1c523ac5209a356215c291b87be28957ef853f0d66eaa99352d515e1d190f947669ce7b0ffa7e74a8f4be996569a5d9c56b6704705b46bb5238d42851f2ac875712bc70b3c30f892019540704d01ad2669a0491936330c95ce7140b2e4939a03638c7e8680ae485e33bbe540d60d3ada162c90a02c7270a39340a4f28b68da4645007a8f6a069a746f73235ddcefc391e12b2e1916824948742c99382473c73404791c617695279dc0640f9502c578c9efeb4095cb4cb0830ba21cf999c6401f4f5a05061d430c8079a02e03b3004311c7d281b5e3cd676c65489ee594e4aafe6c7ae07a9a0a075bbea3a8ea96f047d3935ebc404f04ad29411e08e011d98fed416fd212ee5b05b4d5ad6300c615807f1171eaa49eff5ad418c7c55f8466dd66d57a521f20cbcd66a7247a9283dbe5418a63862479877cf1f6c5008e400bdf1ce684016fe53dfbd1a73794600e08ce3d6800377c8c7d6800a9cf75fd4503d91492460f7ee3d28247a7b459f5fd592d22711c206f9e563858a31f99cfd050583518ba75247b1d134f9aed21396d4669769931dc01c003f7a329c4d17458ac5b55d36c12e040a3f1da75c1cb04ede2447f7f6a94567ad7a66db4fbbb29ba7d65b8b4bd8ccd09c8231eaa07b8ab04a7c2cf87b3f53ea8d77abc72c1a5dabe2452bb5a561fc83e5ee7e541e988218ed2dd22b7855228d76a46a00000ec00a510bd4dd511f4fe84da95cc31f880022da4902b1e7d3e99ac86fd03d631f565b4ee6d4dbbc649009cab2e48c83f514165b8b94b6895c44f279c280839e78ce28178ae6de46748a789e453865570483ec6812d42e85a421fc37918b00a883924d024c6e99b7a2a966c0009e17dc9f9fed40f81c77e28139218e4ff9815b9cf23340a01c907b9140201038ed402fcafd28386464e4fd33c50272bc60032609cf00fbd024f722dc66f24822ddf972f8feff00e280f69b24844919cac9ce7de83a447f30ded823007b50459d6ecacb528349b979127651b1dc795f1f3f7a0990148054823dc5015d491c0a0c3be337c2ff00c489b5ee9c87172016b9b541c49ff5a8f7f71eb560c1fc43e0a47e1aa94277310431f91fa551c1727f29ed409b641c86e31839a3454805739c1f6a026f1fd740f64665fc8c31cfde82db79bb40e9e8f49b62eb7d7e8b717ec832c91ff247fa1dc7df2281bcc9369d671493c422b7911654c1215f92bb8827bf068624ba635392df5eb4b9924558ee5bc19b71cee43c6dc7cf34c657be8db0b0b9d0f51d2afe668934dbf9628ddb8c2b8c0073f3a80da37546a7d25174fd95dc125c69f7313ee5655dfc313bd483cf07b1f6a68d5b48d5ec758b612e9d7293211c8fe653f35ee2a084eb9e8bb1eafb3582fe496278f3e1c919fcb9f97ad03ee8dd017a6741b6d3229dae161057c5750a48249ec3eb4139238568f6a9e7b103b5037934cb3793c610a2cd9277a8da73f5140ee38f6280c4b11c65b934023006d50050030e4647de80c846de3b500fcf9fbd0197273ed4007b91400e580c8e45074a82400e72682b36fd2162b7f25ddc09af2766ceeb872db79cf00f6a0b3229550140e07007a50092db860673de818df473c862686dad6470d9cce3b7b63e740fa1de6252ebb5bd81cd00bee2d800d003a6464004763ce683ce9f1cbe1f1d3a67ea1d1a30b68edffba814708c7f9c63d0fafceaca31e6dc71e1f07daa82608c83819f7a1a11ce149238fd68d0a579ec682cfd27a7c3a86bd10bc38b3b756b8b93c1fe1a8c91f7381f7a034f752ea5aa5c5eb292f732128037619c018f6ec282e5a2cb047abda74d5ce9b6da80f136de4a496219b3e48c92000323ea73467519d3da5bb757dbda410ac90c77c23058f99007ee7ec31416882ee47d23acb5185caf8bab4691b1efe57fff0038a9457ee75a82f6e7429350466b482f2742c0f74241c80c38c64541a9cfa1e89ac0177d33ab3d8de28f2b5bca429f91140e2c7a9b5ae9fb85b6ea9b46b9b3c796fe040768f76ec0fafb1f9505df4ebdb3d4edd6e74db98ee216fe68ce47d280648f75e2485a44da385ddc13f4a025ddbdbea16a633286566ce55f9c8f6c502ad750db2c514f30dec428247e6340bbf04100b73402afb943ed2b9e30683836defe9403bc1e06734020e06280cafe8683a375941d841c77c1a0151b467b50159f00e4127e5402872371040c5046eb5aadbe9b1c02e2f6dad25b89047099c677b7b0140fe3f1010afc803f3018e68160c3041ee2823f5dba92d34db89a1d9e2843b03b6d05bd013560c1748d57aa2797c6b35bab78e6959dc47231580ff336dcfb03c1a58364b5bbb7d7fa7b7427f1f673830c8664285bd1815238fad20f2c7c41e979ba43aa2e2c1cb1b663bede438f3a13c7dc76fb5515e9065b851f7a02950002a09c51a1b83cf14176e90d3645e9ad7752752aac23b3439c066665c827e944d29a6410aea725c4567135bd840d3c88a723728c29c9efe6c50d3ee9545b0bf8ef2e6e3c2fc2c6f72f2920e5f19039ee4938a9a875d03278377acf52ddf867f036ef71923932bfe51fbd3475cdc369df0db4fb389d4ea37970fa9cc0b00511795ce7d4f181eb4cd2451755fc45ac16d637381b14ca36b641dfce723e4053170d6cb52bbb362f6d3cb19241f2b9029862f09f143549ba7e7d2eef6caf2797c66ee17fdfd69862d1a069da7dfdac579d17adcda5ea9e1a992376c4723e39e3b024fd7e94c458ac3e25dee8d31d3bae74e7b79002bf8b8549471db38f5f4ed4c165e943a06a328d4ba605b4b22a1523c420c64fbaf38a82d36f0ce7cf7463790729b53017e940e0b0ceceed8ce0500e1b70daa08f5c9ed41d271cd0132476e7d7ff00aa069797d2411168ed9a41fcc858211f73c5075acb25ca6fb82aa31e58a36c81f561dcd033d42169e158ac64b98151b3981c2966cf639f4a064c7a8ac55e4865b7d493701e1c8e52403ea3cbfda827e390ca3f2c914aa81991bd281cdacc2747215c60e0ee5c67e940cb51b0b2bcbd824bfb08ee1a252d1caea1821cfa67b1fa504982b2283ce08f518a08abb82f6dd0369a5662081e14ce40c7ae1b04fda82275cb0bfd4f4536f7114589a5412461f3e4ce4e0e060f63f6ab2893d3b4b5b5b78e22ed22aae3cc3cc7e64fad3449a22a461500007602a0cd7e3b74c26b5d2ad79147baf34eccca40e4a7f30ff3f6aba3cd0543267eb5427b86f1f4c76ef45d0eca1ad5ef224d13e1cf4fd9b22192fa67bc955f8c8c617fba9fb510d7a6ed3fd43a735e5b54964be658c048fb6cdd9e7eb8a186bac97d174e6d22e23437b7ac26b95e77c68bf950fa7279e2b22dba45b59e97a669fa4ea36aeff89cea9a90451fc355ff0096ad9f4ce3f41570675d4fa8c77da8de5cde5be26bc653171ca47dc1f6c9fed5562b97f70276808da7c24f0c1c63804e33fa8a2928c0e0383c8f7ed41d92a41393f4a2548595c2c37493db4cd04e8a08f139566edfef3445b6e7aeaf65d2df48ea2b11776ae02a93e564c772adef409f4ee8ba9a21d73a36fa579ad9f325afe599171ed9c30a960d5ba0fe2843abb47a6f510fc26a4c36890f9558fcc6783506a1147b510024e30339ce680d2c6ae9861eb9a009178a0205443b989e39cd01d8075e3047ce80563057ca381ed4011c4531e503d85013c91b804a21279c903341131cda8c3abdc8650f6d20c4321232adec3dc504bab2c113c9293bb1963df3408dd4b75e1efb2856463dbc43b4631fad047e9177ad4fe32ea16b1db4b8fe1aa92571f5f5a0916bc8e0895af5c46c17cd8c9ff7da80f6d736f7f6915c59cab35bc837238ed8a072a31c1ef4062870718a06f7702dc5b3c522ee4752ae0fa8230683c75d6ba3b74ef535fe984929149e4278ca9e47edfdab42058003763ed409f88ffd6dfad06b1f12ae612fa0c76e0b471e9916d23f973eb4158d3efeff004a984da5debc1295d8e4018dbf3145d583a2ad96f356bbd7f5d90dc59587f1e79a6392f28fcaa3ee47159444ea3aa5ddfc7acf50dcdc344d7a4dbc317f52641200f6000fdeb41b5ef51d8eab672ffa9e971c97c11638268e431a46000012a3b9a351567db823b11f3ef40948e428048207a8340ab48ae83cb83ee0f3428a982719edf3e68c9cc97d3fe15ad8c9be138f2bf38e7b8f6ef40f7a5f55bdd3f56b46d3649127f1405f08e7249c76f5fa50689d48ba5f545cdcbdb462cba9206411b2b055bb07d4fb1c73528d4fa8f52d62cf47b6b8d2e65fc458c49f8a818795c151939f977a823ba0fe253750eb7fe937b04293f9f6c90be41dbdc7ff006283473c1efc1a06f69776d73bbf0f2aca32572bc80470450284a46dfca19f819f5a04e799614def26c0bdce09cfd85045dc75769d12dc3c3e2491db0dd3c85195235f7c91cfd066ae0cdba9be31f4ec61a386c1ef9d4ee473e45cfb1cf34c101d3ff1ac9d481d46c628ed24751881880833f988e7b0fa5328dfed2f2def2ce2b9b79925b791772ca87208f7a60182ee2b95cc0c48f53823fbd40ac658b30f4f4a086d4ee1d75bb6b78f4e965596366fc5211b23238008fde81f43692da5bc30d97831a0397dc09e3d714087506bf61a2c4cd77324726d2caaec141f9fd2ae0c435bf8c57173ad7876f7a2daca10489121244cdf319ce3dbf5a834fe81f881a6f57bcb6ba7c53c72c11873e28cee1db391dbef4199ff00ea4348116a5a66a8a8a04aad04847a90723f6ad7d18c312ddc02a3815423ba0f63fa541687bd9efe1b533b3c9e0a78473e899e318a09bd0ba6eef543e3b2bd8e9b10064bd9e4da001dc81401aeeb29a984d0ba7d5e1d06d4e6594f06523bc8e7f5c0ac8af752dfc17d7090d9218ec6d9447129ee71fcc4fb9cd6842ab10dc0014f3e5a2c1704b671dfdc734525226dc939e283a362c7f940344a380393df144733e2276e38f5efcd01b4bbbfc3dda4a9298a44395902e4a9c70682660d4265d62de40b1bdc1545054f95c8fe627df141af7c3af8808f3dd68dd5d2a45765884b8908d8c3b6c27b7a77a945d7a5fa474bd2ba8e4d5748b28624955d5d8b13b79ee9e983d8d40a753758c7a46b96f6114725dc92279a2810b3a64f94900763cfafa503fd3b59b79ed84da34713c0cd890f0a158fa1f981de826e1b548959fc4dc5cee24b6467e59ed4101ff19e9f676baa5d6a72c50adb4ad1ac790ccc076200f7ad41e7df881d79a87576a5f87b0f161d381db1c2a36e7e6d8ff3416bf87ff082c6f208ef7a82f22b9761bd6d619785f6dc477fa53705ab57f83bd297ceb1e9caf67708db9c4526723e849e3e94f212dd25d117fd29a8c09a76b534fa39cf8b6b71ced38e36fb73417f52e64548e34007e673e9f21ef590a1c918c90718dc281a69b68f67118d9da5058b798f6fa7fe280daadd1b2d36eae70710c4d263df0a4d583cc7a668fd4bf11b5837d7c93dcd9a3146959822a0e781f4cfa55161e9dd7fa67a4f55b9e9aea3e9f81fc09ca0ba118998fcdb2338c7b528d39f4cd2ba76e2d357d292df4eb391809963420ce1b1b576fa1e7359119f1eb4e17dd033ca172d6b2a4df303383fdeb5c8f2eef3bce4e0e335684cb0c9f354160d36f64b0baf16072b91b5f03391f43c51aab23a5debe91c4fad4d73689e6fc3a290573ff4f03e59f4a3280d67581ce916567f84b58ce0a1fccec3d58fa9a084de08c90464e4d1a8e419059b201f4a05630a176918efc50176293872c17bf14042aa0125b03db14046c60b60123fde6827fa0c68edd5365ff11346ba6292ee64194240c807e59a32b7fc51bfe8bd5ed5db424860beb62b89218422ce09c11c01dbbd0660ae110bf1bf2154838dbebfefeb41a8f4cdac7f117458f4d9ecd2df53b4cf81a822808c47255c0f7c8e7fb54a2ec2cfabba3b4b4b8d3af12eedad40926b0f070a13f9b633649f7a82eba6ea4357d321d4ecad512daf20df26e016507fa4fbfaf3e98f9d067dd2bd2faac9aa4d72d72d1e9510ca46a7631c7a320e18f1dfd7bd059afb7da816d23de4ba5de211346a1e4785f190548e4648c63b64e6b43ce9d5baafe3b539c5b452dbda46c638a167cb281c73ee4ff9340e3a3fa5f5aea4ba58f4bb57dbfcf2b02a8bf7f7a0de3a5fa0b50d2a2d92eb3e048c0a97c867dbedcf6a944e5cf4f6b76d1b3d8ea42795066266c87c81c65b9cfaf15048e83af3cd64abac08edaf01546c38dae4e0657ee6826e5b892de3702292e2545ddb55700fd0fbfca81c4b3bc718716eef9eeaa402280d14ab3c0b2c65c06fe571823ed40df56b217fa6dd5ab9216689a33f2c8c558307e83b8d77a37aaa7d22f2512c28768800c9954671b3d33ebef568d0ef7a7749eb0b5bbbb162d657b32b46d2e1564c8ed9c5644d1b0b9bbd261d2a440af6cb0e2e5b1e7dbc1238e0f7a0375b696daa7496a3a4dac8a92cf078685b271db04d391e40d5ec4586a1716de2a49e0c8c85d3b120f715ba1899173ff305413070abd89cfe9f5a2d3ee9c8639fa874eb6b804c52dc46b20c9f302c3bd11e84d47e1af4d5dc6521d3e3b662c19a58721ff5a9a321f89bd27a374b456d158dccd34d333332c9b4b2afbe47a7cb1f7aa33d2bc0d8c0f1c8f6a2c14b6d501b39cf63450897380c319e3de8065031c038f7ed40d8faf1ce41e4d004876a8dc3cc7e743025c956c818028c904579e7f0e15695c9c0541924f6c00283d0bf07f42d6b48820b8d62d20b2b58d656404959e52f83c8ff00fcfafbd4a35bb06f12391a48dd55cee2b2f3818ed8f6a8158a159890f02242079147623e631c502b0db436d1ecb7458d4738038fb0a087d6eeb508f48bb7d32d95750752b6c26c905b3ddb6f61eb574794f5cb6b9d0fa9678b512b25d24bbe52b8c1638278fbd582c57ff12afaed45b5bc0d0d8a8c08a2731ee3eec5793f40450466a1d59af446293c186cd53ca0c36eab93dc649e49fbd048e89f1675ed35e301e293919dcbf9867b37cbe94a35fe94ea4d33aba6824306dc48015750d86c6e247b0cf63591a40b8dc23fc30f14138dcac3000f9d03687547f12e8dd5af816b13148dddbcd29039c0f6f6f7a0eb5d62caf5636825db70c9bc4328f0dc0271c8a090627d3073ce681acf6505ccf14d35bc2f2c2731bb28254fb8a075144a83ca806792400334049ee6281e2496408656d880ff0031f61fa50446bd76058ea1b9e21025a3bb48afe71df9c7b71de9c8f196a0de23ca7b827d4f7add117e0cbfd4b5059392369663ff004e71c51aa97e8f555eadd258f2bf8a889cff00dc28cbd0bf123a926e96d163bdb74490bca2321c678209ff001591e71eafd7a7d7ef45cde2c20aae144638033fb9ad2e1b5e69d058da431ccf21d4a5c3b4631b62523807feaf5c7a50222f2d648c25f5aeec8c2cd19dae3d3e87e944d3eb7e90d425b49ef2292de38224f1505c3f8724a9eeaa7bd0d57a60406059436306868a7803839c7ad1a158039c13f4a33a716767f8cb9b6b55e1ae2458813e9938cd07a9f42d0b4de99b4b7d1f41b58ff19b03c93ba06607fa8b1f5f619a5b8266d74a65d42da6ba90cce996dcdc8c9fff006a5a2c2635083b05ef83eb5028076341db4b1ed9f7a04651fc41db18ed419d75b744dbea335fcb0db0335f2057901c05da73c8f9d5d18a75174a3f4c47335e35da4ce418a489374254f707d463d33565d1529b569a489a17944b06ec8057d71dcd037b4b6b8bfba31584124b27e62a8a4f1ea68357f83da7ea5a76bfe0912453ccabb49194653cb60f6ce3dfda983d196cd108c2401711f9768e306b2297d73fc6d02773a8b591922693c5004bb9d72542fa2f6efde8314ff867aeeec27500b77bb5670e36ca19b1dff2e7f2fd2837ce8bd5dd348b78b552219022870d9c46e792a4f6c608a0b846c8e03232b29ec41cd0199f1410fd4b24b1e8f712c0a5e4452d851e6c639dbf3238a0afa42ba77475e4ba8470896681da45180b18da76af3c9029c8f26dc1df2b9c606e273e86b743331924f27f4a82c12280e59b008e79f6a2d4d74188ff00e30d203a82ad7519c1ff00b860d11ba7c5e86c9fa3afae6f4091e043e021270b21e01c7dcd6479ab4dd3aeb56be4b7b184cf2b301b57d07bfd2b4bad0fe25e9f6960ba7c7a55ac50cd750335ccaade7723b83b8f6e38a2207a5ba4e7ea3d93780cb616ca53781f99fbff009a0b675a5be9765d43a75a6ad3b25adb4185429b831c70303dfdfd2831eb8954ca48f3827819c71ed406b2b1b9bf9a5fc1c4ce2253238047957dc9345d122b792eee522811a495ce1157b93ed444ff0049f476b1aaf51c761345269d25be269259570c833c6077249e062a68f53e8ef0da69509d4ae225b92a04af232ab16f98cf1f4a5a266d4dbca8af13a329ecca723f51502d14f0cb9f05d1c8ee01c91f6a0393b4edfe63c8a031608859b38f97340d84d04e5846eae50f9829ce3eb400fb24466041f5e3d2823f56d22db57b192d6e61468a41c823ff0035651916bbf04ada7badda5cad6d1b72c09dc33f2a6875d25f0865d06fe2bc6d4c4d3282026cca8cfafcfd29a34cd234a10c768f711a78f1bb392a3001208e3ec69a26a58d640c832091c90706a084ea1d3eeafdadf4f86da3166c0b4b397c18f046140f5ce4d04f4702436e91c28a9122e028ed8a0a9f5a5b6a09a1bc5a135bc72cce048b3c5bc15c638f9d59043fc2db997481aa69dae49e1cb6bb643239211939e467818f97bd305965ebce9a10bc8da9dbaa2679dd9ce3d8530572cfac87566ab05ae9f1490692b9696e1f833738555f96793504df5f25945d2576b7ec16dc46792381c7b7ad5e60f234980e42f6c9c56a82ec3eff00bd4124e49700f1c646e3cd169ce9575f83d52cee324347323f6e3861ff008a23d47d4ba6a75074fdcd8ef317e2e2ff0098bdd4706a60c3f4ae8cd5f44eb8fc3e97248a638cbc73bf90483d463b373e9574685abf42a6b5649fea72bbdeac4a8d3b018cfae31f7a6895b6b29b41d30d8e9f6bbed9213e1b7a994e724fcbb5064bd7835a9752d3af75d8116354778f660788cbd9483dbb0a0cd20b2b8d43528ad2088bdcccf854039cff00e2827a0d34e9da1de896f2182492efc0976f998aa827d3d334113a74aa9a9298628e74570478bc0c7cf1da83724bb8246d3e6416b0384da61b5501c9f5c3704f152c037561a95f5fce61d3ad6db4ab950f34b331dd9f4191db8fdcd406d67a675ab4b6d325d1af248272a43430315ddec7038f6ad4b3f448bf47eb71cb69abddebf21d5e26896203846c30c8603b9c6452d9835901405660376319ac84bf13180779d8bb82827d4fb0a06f777367a75acd7170f1430a9f331200cfceae061a0cf6dac692d7365266191db0578f5edf3a6075a6c9278b3433188a467860d96fbd40fe540471409aa0c1140750001ed8ed4058e15133c983960077edf6a06faade5c5b7822d2d926766cb967da2341dd8f0727d85033d27597d62e2ee3163756915bbf8799d71e2f19dcbf2a092b88dd9a311950a0e5b70ce47fe6ac18af53f5b69da9752dd69da9ca906876e24465d9e69881c6ff005c679c0aa2bfd267a347512c93dbb5d42d90d3c800b68c9ce0ec3cfa528db74ad034db5905ee8be1ac728dc153984f3f980f4fb56453be2de8f647a6aff53796596f0aed46798ec033ce149c0fb0ad71479c9bb9dc3bf3c55a0b95f65a825150b481a407b93c0fda8a29c06671dc93803bd131eafd0af6dffe18d2ee25982a4b04603b7a9c631fad03bbe586381bc5945b96385718c827db3eb5288eb8ba934eb15fc3c535f05427796dcccdec7150637d5bd55d5362b7975aa4d0d919018adec8637807bb60723000e4f7cd58203538aefa8aeb478a7b9beba924547b8774cf8608036a80704639cf1f9855d1a7f4c68b67a03de5e5d59dad8d988c62e1c0f107a1e7fdf7a082ea6d07a6e3e99375a7cb6b3db093c727701e2360f7f53dfb50653d4130d42ee18f48b3f0232a15218936963ebf5fbd06dbf0cfa74855b9d46e04b730c6144691e12307d33ea7de8348ba6b5478a279a004f98c479247b81f5a9438805ac0be2e02e73c9ef8fbd40c2346d43578eefc40da7da1dc8b8eefea4fcb9fef419beabf12a4bcebcb2d2fa7ee0dc58492084b30236bb6467dce383f6a0b87556a67a7f4d95a0bbb5468816f0a69c78b2e072572719ce78357079dfab3af2e7a92c963b88d94abbbf91cedc93edf418aa2c5f0dbe2a6a9a0c90d8de34773a6a8da1186d6403fa48fec682d9adeb7a9b4c9d572dacc9a6c9700456e5ca910e000ecbd8e580352fb1ae7476bd6dd49a325e5a9f3025245fe961dea097523cc0919a032af039a006936c81423104649c703ef40dcce64bc3035a87b6f0c378f9fe7cf2b8fdf340a4b6e25962915d94a67807839f7a043586922b5636ec44c061063f31f6ab079d7fe19b7eb2d4efeef55d5d74f992e9a0fc3a441dcb13927b838c9aa2d4bf042c618e178efee6e18104870172318edf5c1e6945bbe1a748ea7d2315edbea3a99bcb190030c401010e4e783ee0fa56455be3d6b90c1a6268d69e17f1486900ee98ec29ccc183119419e7e55ba11f089f523ef5058363a8059fb8e31e9421b491056c01819e28d3d0ff07eea3d53a1e3b6b8db235aca63c139c0eea68ca47a9fa6ef757b83ff00bf68ad428c2f248c7a8f9fcea518df516adac74e7544f63a2ea172f1800291e6cee19ec78cd5826344e85b6bad25ba8fade5b99dae0ee11efc71e858f7e7d054a2d7d39a75ae8f7b6b00b8917f1516624b78429da327cec493db1db1d8540cf4aea28f58d6aeae2f6dd64b498082d880488d149fcea7d4939ab04175e6850a8d32de3b78e380c8de32c4db4e18e430fef543cf86fd0d691b4fabdf6648b3b2db69ce7dd87be68342d2f4fb9b5b891af1a28a2dc05bc5036d001e0eef7352884b961a2ea9aa7555c885e08d45b5bc52b61b686c120fb939fb541276bd4b61d53624d942e2f6200bc32290633e99f4233416dd3ad3f0d611c0c77b632e71dc9ef41156dd27a45addcb3dbd9c513b1dd941821bdc7b558333b9f873757fd69a85e3f813e9c7723b5d93265d872473c11544a68ff08fa75e290b42ec4e4124e70738fa5048e89f0f745d2aeadd2decedda6525c975121183c77f7a945c754d0e0d563682ed43425369403bff00bcd58308ba7d5fe13f5a05889974a9d8b46aede4914f707d88ff001528ddf4fd7edb54d1a1d56c312dab2e64dbc9418e78f5c541296d70b716d1cd6f8789977230ecc280cb7519b816f212b205de4e0843ce300f6cfcb39a0545c42cee88e0b458ddec33ee680eac92266360debc7b5056fad2d354b9b189745744be121daf27e550548ce3d4d58324d07a725e98ea2b7ff5381f5169a7579d021fe13904ee43ddfbe49038ab46e76cf05cc714f6d309232a4a98ce54fd6b2196bb7f2e9b631b2c427b891b6851db3eff002007341e5bf887aa2ea3d4f77378be381e42fdb711ed5a1554395caf1cd07617dcd04fc85402101da791421b49920331381c60d1a69bf02f56f03a925b12c162b98c955f775e47df19a32d99b518268e4491668704a79d4aeec7b7bd4a30feb7e9144d76e265697c3e2693631674273803e556087d76f35fd49859e9925ccf611141106f2e182e3241f727f5a94681a268f79ad1b1b8b9dd66b1c2b1ce9bb06361c1e7bf3fe6a096b0d3ba57488e485b52b40909c386901607d47bf7a0ae758eb69ac4d15be81a748f0a9c35cc90b2eff4c03c1c638a0b77405c5d5d45f87be5fe359a88b81b401dc1c7d38fb50586fed18ea3015790091591e447c1518c8c7a0a0a5754d8c9d49a8d9f4ee9dba0b3b5224b9692327728f627e7c6682f9a7e996b6b3a8b6b748a348820c7720761412c064e3041ce282b5d4bd73d3bd3f33daea97ac2e540dd0a292dc8cd043c1f15ba2a7923b65bb910371b9a12141f9d02edf13ba2ade56857551e5e77244c54fd0e280746ebfe99bbbd655d56dcdc9ce08465565f4ee3bfca82d53eb3a6dac3e25c5f5ba646402e33fa77a0aff5b74ad8757e9ca972844aa37c520fcca7d3f5ab067bd369a8f467544d626c98e9f7118f0200e4465c903049c8c9e6ad1b24334b6fa6249716cab20037c309dd83db03b5640dddac3764a4f02cb1103863919fa7a1a06d6f600c37162911b7b252b87dc773f1927393f4a079f868edae1ae6328a8b1ed38e30050226e85d5dc1f879011b3c47c2f604719f9d01eff4f4b83e3c6b18bb452b1cac9b8a83de80b16e8208a3b7b58e1407cc061427cc0ff1560ce7a8f592d69a97504cad2dac01a2b53900c3e9e51ea58f727d0551e73bfb86b99a49a46dcf21c96340dc13804f20f6f9501c0e3b8a0963316fcc4607007f57bd084d64dec01200ce483468ff0040d525d1755b4d4206ff0095207c11dc67ff0019a18f56584f6daad9dade4211e39104a8ded9152b235cd8c530613229c8c1c8ef50472e81690ee00322b0c100f0debdbb7ca8111ace856371358cba85aa5cc407891ccf83f2ef4048b4ad2e59bf116769672c72f99dd1437239078e2824a4d3e1b94559234110e781839fa0a0561b38ad532a12319c86c6307e740a9732a3a00cac870cd8e0faf0681be8b6db965bb909df3c85806eeabced5a09523647e6e0fef419a6adf116daf7ac34be9dd1da686e7f1ca2e243b76320ce57df9ff1560cc3e3f470ff00c78255b842b35bc6c4af9b6e323d3e95467b6365f8dbcf062beb68c119595d8aaff6e282422e9899b4f6bb5d46cda2562a76316c1078f4a0859e1b9b762c0bf94f0e84feb4125a57505c58ea70dd5d0174a986d92b1c13f6f5a0de7a5be366877260b5d42dee2d2423124a487507ebdf15289dd3fac7a7bab6feded74d61733473acdb5a162142ff00313d81ed505fa58fc6d809380c1b9f5c502e0e05040ea367a85dea454de2ff00a610375b04c16c7a16ef8340b5f6930dce9375636acf6a278f04c5dd4f1dbf4a084e91d06f3a52dee62bbd4a2b882494ced3c8a448063b63b638fde803ab7ae749b2b3096d792c93c8c109b55dcd18ce3710473ffdd043dc758dc5869044565aa5dda4c3c2b7bc78c1f14e3963db03e7c0ab066bf1327d41ba76ca6bc48ecad24c456f6b0c87cf8e4bbfa138c0fa9aa3297c83dd4e28395811cf2680a5b93c7ed413cd1ff0f3c797b8031406645236b0508406f30e68ba49c051b97d0e0e7d28ad57e19f575c5be8f269515dac772877c11bc464dea7ba8c739ce78f9d3193bb8ebfea2bcbd6b5b6b8b58bb7f13c2f0ce31cf0deb4c0f2dbad6d743d2ee99efae752d6c02a86e0054524f6383c7ff94c0b6af274c75149a46a5a82c46f1e1479fc3190bd8156fbe7f4a960bf74e9d253f1167a3ac09e0856610e3041ec7f6c540f67b892cee7f8d18368232ef2af2508c7047cf340ead5bf130accc9b1186541e723d09ffc5033bbb1b82d74d6b37f1244daa1b38073df3f4a08eeb1d3b50d4fa6a5b4d32f12cef1902ee73e523d476fde8306eb0d3fabfa4ba92c278af67bb7281606472f90bdd58558253a6afb40ea1d62283a8b461a66a6f931cf6a7c2466f7cfb939e7b5515fbed3747b5eb8f06eb78d35080a2ec9719c76f98049a0b4ebdd37d1bad869acbf0b03c5c16b29444adf50ded41995f68564a263a66b31cd02be152505493f51c1a088bab69ad1bc179e320f07c37c8a0692b46c4995f0381db39a0b2fc34e971d57d4705bc8db6c50ef9dd97b81fcbf7381528f5ae97a1d8e996d1db69b0c7648855b10a81b80f43c739c54134147b9a036063279fb5046e957726a0f2cfe04915b06db1788305ffeac7a0a00d72f8d9c491c06337533050ac7185cf2df6a06da2da4293488f34973328c34aea428c9ec3eded40ee7d2ad249448f6b133820ee2833df3fde819ea96897461b05b87815f2ee919e5d47704fa039ab079b3e326b70eafd4ef6d6650d8e9ebf868b69c8247723efebf2aa280eb9193ebedc5002a124e015340018fb8fde82cf32b1603d0678cd02406dce3008e47ce81b499c331383c9c9f5a2e9c69377369f7d6f796a4acf148acb83fb511e91b3b3d0bab745b7d45acedd8e3732b71b1fd73f7a5a19eafd09a56a0a96b1c705b49c48510761ce4fcfbd4d0d752826b2b583476fc3daacb295b79d768de8a32b1e71f989e49f6a7d14dd1af5ba275a45b8b093c054492ea769092373765c1da4679fbd306e36ba9595fe9f0dcdbcc92c33e1579cf27d0d409ea178f68521b6b76926ee8a7853f7ff140bc768d78f6f73748d1cd103b543f0091cf6efc502f7319dac194371d8b6326829f0c501d7ae6fa568d5d4942c806d4db81839f53c8cd59456fae6e628749b5bab8b1865b08e4726588ec11e7f2e49071c93da9a31dd4341d675e9a5bad374f9858162d0b4ac70e18f0573df35a0c759f87bd53a404f174f965dfff00f479b1ef570576e34bd4b4cc0bdb3b9b7258a00e846e3f2a94376475cee4914af7ca9150685f09ba61efb52fc7dd69bf8eb7c158d1d0b47bb38f37efde968d6eeb4eb5e91d6ad25b660aee59974db6881690918e31ce39279e062a5a34bb57b88adedd1e379679065d80036679e6a07e8391bce7e940c659ef5afe1286de3b16f2b8903094b7b2fa7ce81eb380c4260ed193f2a0cd6fa5d4a4ea0fc7bdadcce923158a3039db83c038e3ef41a0e96b2ad8a35e009291b8a939d9f227e43bd590436bbd6fa269202c974b7123602c76e779624e00e29833bf897d493e896525dbcb2a6b5a9c3e1456b91b6d60cf989c7f31f7a60c02490961ebcf3eb541308e39e067b507007b96007a67fb50178f97eb4165ce18165c2927b773fad023202d9c8dbb7818ff003408300b87f2f1c107d0d0c15a4f2e339c90467f6a18bdfc2cea8ff4bd561b4b9ba686d6e64552c4f954e7d7e46a60f4688d240af1b2bc6cbf5047ca960617ba658de1b792f2d94a5ab33461b18524633fa1a81b5c8b5168967369d23c0e0a24622dc981d81c76aba29df0bb48d660d52fceb88d069f04aeb69130037127f37b9c0ed9a8350781240bbc06da72323b1f7a0eb8816e633192ebc8c9472a78fa50349b4c83c068e24f0ddbcc1c13b837be4d055b57e98b996d4db5b4a893dc1e6620b6ccf2c467efc504ce97a38d3f4d874bf09af6d46e2f25cb82724e791db15650a43f878b51fc34f3da8f132b6d6a98c80a39ff007e99aba249631b58b9047239ec3e55368aeeb7d2da6f52c0eb7f16e87f2c6e836ba90724ab7a67b55d115ac7c3e8aed2182def4c56a14096368959a423d77e3229a27b41e9d8343b01069c8a8dc9660aa3713df3c64d4a1c695d3d6b67a8cba94b9b8d4e61869e4e4a8c636a7f4afcaa09a485519caae19b966f7a0435196582c656b74df3e308beec7b50629375775b691ac5bdb6b16d6378779f019b00a31cf391c9c2f1daae0b35ef52f5374de88d77aa45a6cd25ddc0108694ee2188c28007603d6a0d16c92430a4b2ed3230dc401855cfa0a0a07c45d7b5db9d462e9ee960b14b2ee134ef8c850012147ec78ab0670b643a2efae753d72686e6e2da211db42176079c8e768f65e39f7aa332d6f58bbd635096f6fe6692695b24f603d801e82823cb900ee00e68006460051dfd680ed9f0c905b713d8d006d5f5419fa505a18f94e40501b1b81a04186d62402c87be3d6810b81290aea8467201231cd1749dbc437f9f1e201db3de8ba07dc0175c027f28a335b17c26f888d6b6d0e8fabf892a29c453b1e547f49f7a946d6424f08236491c833ee0835073294888894120700f0280813c40a6711bc8843e00fca7d3ef40e41dc081f9a811681c6f7565329185623b7e9de812b3bcf11ff0b74563bd50494cf120071b97e5fda80d7577046c9019d5669dbc340324eec67fb734103d5da96bf67a7cf0e916f6e2765f25ddc4c11107ab1c8c647cce2816d3ec7f0f6564cae6e67da375e6d52cc4af2e4fb13ed4145f899d47b3499f4bb6d46cda49b69b92921565c3648e3dd40c81cd5c0ae89f13ec246d3e379ed2d6da180b5d34849da1780b128e49271c9f4a60ba685d5fa36bc42d95c324ec7090cc9b1d87b81ed50588958977cacaaa3b9341c655f12348d1dcb8dc1946540f99a019e2134454eeda7bed3839cd052fe2136b536b5d3563a1ca53c49da4b9507198940ce7e5c9fbe281c6b7a974cf4ee4ea7242d76dc784a3c595b3e9b464e3f6ad0ac745ccbd4fadcbabea42da56959a382ce7460d6b1a93c01f97272093ebf6a82f1ad6af0e9da5cb3cecf6902216919f82aa3818c7a9f4c530649a9f5269ba7429d472239bc991a1b0d3c3152880f0f23039e7bf3de90635ab6a377aa5ebdcdecef2c9239e59f3827e5ed54302195fcc38cd01245395c1f5f4a05b606538e483c501b6939e3b5077860f3914165754c33e549000dbe87de813b820c27fa7baafb8a04a69c98e281e42618c795338033df1f3a06c03e4e029247007ad010093c35674da71f977640340081a190658e41c820f141b0fc33f8926c218b4ed609366a02249bb2d19ce3ea4528dbece68eead926b7916689c643a9e0d643387521fea2f693c2d6efc786ee46d9bfed3eff2a04669edf5295ff057a60bd865309246d3bbbedc1efef41d63a8dec9ab4fa7dd4510fc3c69234ca186e2d9c003b7a67bd034bad0a5bb96e25d575267889cc1b54446d9bd0a37bfbfbd02925945a72cba8dddc48b3f87b1e58f23c623f292bdb7fa7cf38a0a5750f54ebba56a9a67fc516b6d6fd3970ea9234677c8dc7f38f6e4640ce282d1ac4b16bfa72c1d2bad430cd1ba822061865f5007d3daac19cf547c189357d561bbd3eee683c62cd786e9b73337b8c7bd512bd39f06adedec2de0d5ae639da372e6485363107f97767b505cee755d03a5e58ac228659af123184b7b733322e38c91dbf5a943ab3d52e64b49ee755d2e64950e238e35f10c884e17cbe87dc540e6d7509a4f110e9f7566a471712850abf6ce463e6280bacea36fd33a4497f773cf32c698dcc4beee33938edc7ad05534aea683ae61d64c4d2a69b6b88d16d5ca5c303f3e386cf61db140e27b5e99e96b64bdd562b6b30aa36c6c37cac7dc9eec6b42c1a66a962fa70beb6b516d0cbe76322f86c78f6c66831bf8b5d5d2dfa35a5dce60b1933b6ce3c788769f2b331ec1b8fd2831b79649984b239773c1dc68129725c1c640e73400ec781d8fb1a03c4a85d0c8582640257bd01e51fc42236263c9c67be280429c6037eb405dbf5fd682c2a0bb976cf07d3fc5009279ef8ec4e68193a9902b28e7dc71fb501d95b098e0f6dd9e0d0049131019b047b8390281bb292484e47c8500c4f242c3076bf704704739a0be7c3febfbae9a5daf23cd017c7e19fb107bb67d0f6fd6837cd2757d1fab34f4f05e37dde630b1c3a91edf4f7159103d6eb7da65fdbdf59dadb5e2460ac876ed9e1c8c060f9efe9c8a0a75cfc42d5742d2ee5a7e9dbb494b6d6b9bc930cce4f940e3cd81ed4160e98f88315e689fff0022b57664199cc5196f0c7a164ef8f98cd0589baffa68590985eb15c0db1985839f6c2919340b69d03f5285bdd6f4bf021424db4329cb153fccc3d09c76a090d3340d2f479a7bab3b38e2924e5e451cfd280d7dafe936f6c5e4bd89813b02a36589ce318a0358dc35cc4e17f9bf234cdbb78fa0c607a7340e6cec20b1596610c6934b8323226379edda81da8dcb9ec40a042f50b5bb21645473b58b11dbd7bfca8304f8add5d67a9ea8ba5d8ea72c1a4d8a952f10f2c920e368cf71e99fad5833dd0754d6ed66bdb2e9a91a5babb2a310465a57c1ddc1038e7bd5171d3748b8d46ee1ff005298dc6a764c27d4eeaee7fe1c01795881c9e7804fe940dbe287c4b6d75a1b1d1c986d62277c91bf131f4c0f6fad0663737135d3b497124924871f98e7803007d2811dc5b83903dc0a0333f03be7de8122df2c9a05a11e5f51f7a05ce7071804fca8033e5da0734020b0183bb23e5416269577ed0e5323078ceeefdff6a03dbcd62914c2f629a47c622689800879e4fbd046f9d8a2a03e31385c0e73da8b83ca590947dcaead8208e73da8849b3e19ce704f7c5015586d006431f5cf61f3a04ee586ff002481c8fe6191408f0011eb8e30682774dea9bbb5784492ca6385832e1ca95e3d2834be9df8c312e2db5eb4375080337000f1303d18763591a469baef4d755989ec6f6dae5a23e20b599406dd8e080ddbed41272f4dd8caf1c86d163910f9595882a3d718a035edd695d3b6a926b57d0ac65b10b4e06eedd863bf141077fd7af2782bd3fa26a1a8891d57c630948c0279393dcd04cf5875258f4de9f0cb7b7b6d66d2b81ba752d85f5214724fed41036bd79d2fe319d7a8f4b9c81e58de2f04827b9ce09a07a3acecf54b790685ace8697606009e52c377b7f2e682b097d7d36acf0f55df5edbdc0977412468cb6ce3be10af3c63b9c8a0b0751f505be9690dd5d752436f62a3fe4c6448f3b7b0c64e38f615734651f107e3045ac42b67a7693018633b965bc1bc838ee173807bf7cd33065baaeb1a95f2c11dfcd2bc51fe48880aa3e8a062a8b059f595df4ae9a74de9e9ec499d43c97b1427c6e47e525bb63e4282ad3ea3712893c599dbc4259c1627713c927de81043950df97db1406da8411c92063be280230839627078e79a0390a71b5bb5003a8c1232338e4507025573e9fbd02a0e41dc0e680c3691cf714053bb34160895dc16f291d98d02322aa39f3e14707ffaa06f202a5bb0c7201f4a343aca51090497efdfbfce89840c8db8e46573923ff14410b00490d9f5c1a0425dd8ce4673e873cd0265e4dbe7041ed814009b8cbb8e5863bd07163b7716e0607b6698060b96b7b9478dc8643918247ee39a60b7e97f133a8b4e0c63d4ee597380923970a3ef4c0e13e25dfcfab457ba95bdbddb212016501867b9cfbfda982f907c74b282da34874a9048aa479c83838edc62982b7ac7c42d235cd67f15ac5b40c366418a2cb0c1c81e6f5e31db14c160d035de8cd4a3f18ea96562cc37359dfe9cac887fef039fd6b39446f56ea5d13a9dca4579a922496b1975b8d22dfc3566cf9557230703be715ac1431d4d2275325d7fae6b4f6f182a93ef1e32a9f41938f6a60afeb1a95c5fea53dccf772cf2c8c489240031f627e7565c0d67bbf160487c1801073bc0c31f91f953420f2bc8c7c52cc540032738a809905c0f4fa501940208e73df34028e703938a0577ae013f4a001300db4f03b71407461ce0502dca8c9c7dcf6a003fafcbdcd0070bc1e0fd734070db467b8a04cb9c9e68274b93bcb1daa40200ed4099765249ec476cf340849b8b264823bf34689ee009cb671df1409bc8e8b8e770e3ec68984d9c953cf97be2860b248caaebc107dc67f7a184c31232db88fd451031ce50e76039f5c8045026efb8f93279e0fd680b239504f0483d88ef409ee25bb90c79c0e050151c6e21b39ce783eb40adbcc2cefa17bdb61322387781c950e3dbdf9c8a066f28790b22e013db3dbef54726081e63c6460d34191b1bb0720f634060e7600412c781502409c8e3d7b500ed71dbef8ed40243f181c0a02e5d4e0fad006f644e4819e3b501f7e3049e7b501bc43b4e391da80558003392d40a23305e320d02e64cf998e1bf5a032b0c927b8e68049c8c8e71c6280377043118f4e680bbff00de0504ddbb3128371c1c64668024e59f3cd02521254e4fad1a2107e48fe6a6809ddb9e78a029e1463d05027ffc744a6c3857c7b1a205ff00e637fbf4a02b12b1794e39f4a02024e7249ed409924720906800005173fd7404989698ee39e4f7a04cf723d07a501fff0097ed406ffe36a018ff00281e99a037f4d0731f3bfd28007e53400ff99a810248c0cf140bc60123233cff008a0557f9beb4056eff007a07109243e79a03778b27bfbd02b128c27039a054001b818a06609de793da815006070283ffd9}\par} -{\pard \ql \f0 \sa180 \li0 \fi0 Here is a movie {\pict\jpegblip\picw20\pich22\picwgoal400\pichgoal440 ffd8ffe000104a46494600010101004800480000fffe0050546869732061727420697320696e20746865207075626c696320646f6d61696e2e204b6576696e204875676865732c206b6576696e68406569742e636f6d2c2053657074656d6265722031393935ffdb00430001010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101ffdb00430101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101ffc00011080016001403012200021101031101ffc4001a000100020301000000000000000000000000080905060a07ffc400231000010501000300010500000000000000060304050708020001090a11153976b7ffc400160101010100000000000000000000000000060800ffc400261101000102050109000000000000000000010200030405061121b33134365154717475b4ffda000c03010002110311003f00a90cf388f366a62aa720ed6ae07f96901f3831d973452b8cf36fe3570fc908e46d466433e5dd954f2e96992d9e498c7753faa44916e016ca91cc7d88b38fe60a5b97737defcbcc539c98d336a57f4fc2ca9a486bf07ab575ad9a3af4df221d8215e36df86c4504ff0024574551b3d687ee0575757b3ad64e311ee62bd94158d37e24198c43973099f1fc0c41614d950246513a081abf76cfe7061f6863281e6352fd1670949c148dd6dfb0d25f5b3689b1d5c965b0eacbf4e0932ad28e22ab9ae945633f4744bd3c8cee0a7fdf085b9000f449c5f7afa30b83e0b6fd7b0c8429c9467ff9715347c891e25fa24a205861aa715e6a09bd0488237dc2723414d9891381524e8ca7c0894664f835653631ab55ee7e3de433e4ff001b30949124e4c10c8b6ad0a479b3f9c937b2cf5bc0095ad600a0a41a0e9faee174a1c605e161c6c7a313539650b0113190f1a8368e60d5b24f30ff008ea7f0bf867fa6595feeb6978f1fe0f9c26177f4d63a51a9235184750e7d18811339cd000000c75f000e00380380ae390c350def826ed42ad051fa6f501c50f9b699c3b69cbeb76476d202bf3ac985b6e0e968be66572893e6a744540bd9722e5c87956848629bc2559306bd113e8653d3b6aff651dfad7a3ac8b02958cba02a93ccf525757039bae6cff090e1d90688e8aa233ee86a4c4a3e0586d6b2340522e47dcb7d0046d8a5acb05a123ee25d2b230b2ada6e2e2f9ede3c05202520ec2487b0d56562529d8b3393bca76adca4ec1bca508abb001babc007915d84fe3dd14e207e3c62f8379da2a3b861fb6629d28dba53b6ea388ebfed866bf6dfb553455e91ed547ae92e9445253a4fdf3efb4f8ebdfbe7d3c78f1ee0bb9e13e358e942a4ed49e22cff00eeb35fdd7ebfffd9} icon.\par} +{\pard \ql \f0 \sa180 \li0 \fi0 {\pict\jpegblip\picw250\pich250\picwgoal3000\pichgoal3000\bin ffd8ffe000104a46494600010101007800780000ffdb00430006040506050406060506070706080a100a0a09090a140e0f0c1017141818171416161a1d251f1a1b231c1616202c20232627292a29191f2d302d283025282928ffdb0043010707070a080a130a0a13281a161a2828282828282828282828282828282828282828282828282828282828282828282828282828282828282828282828282828ffc000110800fa00fa03011100021101031101ffc4001c0000000701010000000000000000000000010203040506070008ffc4003e100002010303020404040502050500030001020300041105122106311322415107617181143291a1234252b1c115f016336272d1082443e1f1265382ffc40017010101010100000000000000000000000000010204ffc4001b11010101010003010000000000000000000001110212213141ffda000c03010002110311003f00dadd18a10a704f6a95ccc57e37750782b0d8d9ea0cd32e7c5446e07e9f4ad723119a7b89e61e348f260719278aad613cbb640002938c76a182b264fc87bd13009c0c019c76e3d68a072e1cf6f4cd502d330c28269a61bb39c923923d4fad44c08dccb95cfd28b8280769ee08a263891e1808739e4f1d8d149392172cc714050dbb9fde8960ed8c60b79b1ed44103b05c331dbdb1dc5026ac1946d20ff8140aa631c773ec738a0346a003bf93e9cf02801895e7b9a01886796c923bd0090a06393c76a0142003ce3d86680d8dd9392303f5341ccc1b3cf7a2c812c37e4923d381429757013209fa511c18146c9247a0f6a007900c0c671c6280854e086c673eb45c27c038fd68aedff2fda836ef881f136f25d5e6b7d1262964aa02b03f98fbf153131935edcc97576f35c33349212cc4f39f7ab26186dfce5b200f73451f7600dcb8cf27e7400c0b291914046c9e0718fde81371b8e7273f4ef4007691919240e714097f31f376e7b5008caee27807b0f5a02c8e1b3c6d27d33cd0201d839523144d1a149ae084b78da47638211771fd050d582c3a0faab5119b6d12f8ab1c06788a0fd4e2ac356fd1fe08754ddccaba849696309e598c9e2103fed1dcfdeadc44fea5ff00a7f956366d375e492403ca935bedcf1eea4ff6ac68a55efc1beb3b552574f8e7009ff933a927ec715bc82b3a8f4d6bba5ca1352d22fe061cf9a0383f71dea5119cc6c0baed3eaac0f1fad40897dcc3d81f7a052366c1007df3400f21edefc5008c28f30c9c5170ee4fc37830086395250a7c66770c18e78da31c0c63de8609b41f7c515c5172a30c3b76344a3e377cb2339cf7a242aea89808cce368272b8c1a2e107c672a49f5c1a181c9c7ae7da8a2119e7b1f5068099ffa68258a132062d8f9e0f34059502b61bf2824e681bb297ced2a71efda80f19c47b9c77fdbe74057c13e539cf3c1a0eeeb9c73f33405ddb4f18249c1e28062b79ae242902024465b9214614649e7bd0362a7249eddc513456e5720f38f5a1a98e96e95d6baa6ebc2d1ad1e65521649bb469f563534d6d7d31f04347d2a2fc5f535db6a0e83718906c887cbbe5a9a8bef44dce9f731ca9a2e89169d6d6f2184b1455dc07b11dcfeb4d16f119c649a681285b03d3e5500f87820ff006a0e098191de80ac9b8904647b55d11da9681a56a31f87a869f6970b8ffe4883629a289aefc16e92d441682da5b098f21ed9f033f353914d19b751fc08d66cc16d12fe2bf45ec92ff0df1fdbfb559ec667aff4eeb1a04db359d3ae6d40eccebe53f46ec7f5ab82263da7dcf3eb5174e5181076918c7de869503232491ee4515c1803824f03b51287f30e0e7d803449494832c157278a2e8c71fcb9f9d144639236824d01e142efb1768cfb9c7ef40512a818de78ff00a682518e7cc30ab9e00a02cce9953247bd41e467191ed9a04205ee99da4e4e3d283a524b0427b5026c18a8e082067db8341ce0e39ed409b6502907391edda80f2dfdc496f0c124ac6184b144cf0a4e338fd2894f7a7342d4ba9b568f4fd261f12571966270a8bfd47d8511bae85f02b47b7fc34bac5d5c5dc88a0c90ab6c8d9bedce3ef4d1ad691a6dae976a96d616d15b409f9638d70054a1dbc68ea51d4329f4619a8022b78e04548515117b05000a035c5c4702a995c26e3819f534047bcb68a458cce866719540724d02e41c0f7a012a40f6141cbc8e7bd01719e38e6838af1c0a04ca8206d3cd037bdb082fad9e0bd8a39e0718649141047d0d5d18f759fc0cd3af164b8e9999acae4e4f81236e898f7c0f55fed574615aee83a96817ef67abda3db4ebdb7f66f983d88a061bb8db9e3d45165076db83c1f950a53780d8247c80a2398f182724f1c7ad080c608cfa7a51a0062adc7afbd0130173bb9c5070f071cb37e82826106e8f615e01c9e680d6b35bc534be3c1e3831b2aa962bb188f2b71df1de819ae4b1048c7f57bd01a58268e332642ae0704f7cf6207af6a01b99e17b7b6416e227407c494139909ed9f4c0a04a4e501e0f1eb40d263e53dce7fa682c9d0bd13abf58dd6db18bc2b157c4975270ab8ef8f563f21447a73a03a1f4de8eb031582b497328066b97fcd21ff038edfde88b7e32703bd64188e7e6283864b73400cd804b67ca3268317eacea6d56ff005233592f8b6303f953fa4af7c2fa93417fe98b763e0ea171297bab98558068f695ce0e08fdbd281e5c6a57ba5e9d14d716ef7774f2ec112601da4f27ec2827ada74bab559a20e148fcae36b0f91140283729c77a0e0a7777a01dac68395719e39a029607cb901b19c501480ab9279f4a086ea8d0b48d76c0586b7143224a76c61ce1831fe93e86b43cd1f12fe19ea7d2533dcdbeebcd20b612651e68f9ece3fcf6fa5067cbcf20ff009a051724905411e94032799060723da8406d6c67e7ea68d0e1770fe5cfb5026c37039ef9a02eca098c91e6e01e71c500b1d8a49c12786cf6a06a4e256008e3d050119958007920e2801154e32fb4120927b014017eb1c523ac5209a356215c291b87be28957ef853f0d66eaa99352d515e1d190f947669ce7b0ffa7e74a8f4be996569a5d9c56b6704705b46bb5238d42851f2ac875712bc70b3c30f892019540704d01ad2669a0491936330c95ce7140b2e4939a03638c7e8680ae485e33bbe540d60d3ada162c90a02c7270a39340a4f28b68da4645007a8f6a069a746f73235ddcefc391e12b2e1916824948742c99382473c73404791c617695279dc0640f9502c578c9efeb4095cb4cb0830ba21cf999c6401f4f5a05061d430c8079a02e03b3004311c7d281b5e3cd676c65489ee594e4aafe6c7ae07a9a0a075bbea3a8ea96f047d3935ebc404f04ad29411e08e011d98fed416fd212ee5b05b4d5ad6300c615807f1171eaa49eff5ad418c7c55f8466dd66d57a521f20cbcd66a7247a9283dbe5418a63862479877cf1f6c5008e400bdf1ce684016fe53dfbd1a73794600e08ce3d6800377c8c7d6800a9cf75fd4503d91492460f7ee3d28247a7b459f5fd592d22711c206f9e563858a31f99cfd050583518ba75247b1d134f9aed21396d4669769931dc01c003f7a329c4d17458ac5b55d36c12e040a3f1da75c1cb04ede2447f7f6a94567ad7a66db4fbbb29ba7d65b8b4bd8ccd09c8231eaa07b8ab04a7c2cf87b3f53ea8d77abc72c1a5dabe2452bb5a561fc83e5ee7e541e988218ed2dd22b7855228d76a46a00000ec00a510bd4dd511f4fe84da95cc31f880022da4902b1e7d3e99ac86fd03d631f565b4ee6d4dbbc649009cab2e48c83f514165b8b94b6895c44f279c280839e78ce28178ae6de46748a789e453865570483ec6812d42e85a421fc37918b00a883924d024c6e99b7a2a966c0009e17dc9f9fed40f81c77e28139218e4ff9815b9cf23340a01c907b9140201038ed402fcafd28386464e4fd33c50272bc60032609cf00fbd024f722dc66f24822ddf972f8feff00e280f69b24844919cac9ce7de83a447f30ded823007b50459d6ecacb528349b979127651b1dc795f1f3f7a0990148054823dc5015d491c0a0c3be337c2ff00c489b5ee9c87172016b9b541c49ff5a8f7f71eb560c1fc43e0a47e1aa94277310431f91fa551c1727f29ed409b641c86e31839a3454805739c1f6a026f1fd740f64665fc8c31cfde82db79bb40e9e8f49b62eb7d7e8b717ec832c91ff247fa1dc7df2281bcc9369d671493c422b7911654c1215f92bb8827bf068624ba635392df5eb4b9924558ee5bc19b71cee43c6dc7cf34c657be8db0b0b9d0f51d2afe668934dbf9628ddb8c2b8c0073f3a80da37546a7d25174fd95dc125c69f7313ee5655dfc313bd483cf07b1f6a68d5b48d5ec758b612e9d7293211c8fe653f35ee2a084eb9e8bb1eafb3582fe496278f3e1c919fcb9f97ad03ee8dd017a6741b6d3229dae161057c5750a48249ec3eb4139238568f6a9e7b103b5037934cb3793c610a2cd9277a8da73f5140ee38f6280c4b11c65b934023006d50050030e4647de80c846de3b500fcf9fbd0197273ed4007b91400e580c8e45074a82400e72682b36fd2162b7f25ddc09af2766ceeb872db79cf00f6a0b3229550140e07007a50092db860673de818df473c862686dad6470d9cce3b7b63e740fa1de6252ebb5bd81cd00bee2d800d003a6464004763ce683ce9f1cbe1f1d3a67ea1d1a30b68edffba814708c7f9c63d0fafceaca31e6dc71e1f07daa82608c83819f7a1a11ce149238fd68d0a579ec682cfd27a7c3a86bd10bc38b3b756b8b93c1fe1a8c91f7381f7a034f752ea5aa5c5eb292f732128037619c018f6ec282e5a2cb047abda74d5ce9b6da80f136de4a496219b3e48c92000323ea73467519d3da5bb757dbda410ac90c77c23058f99007ee7ec31416882ee47d23acb5185caf8bab4691b1efe57fff0038a9457ee75a82f6e7429350466b482f2742c0f74241c80c38c64541a9cfa1e89ac0177d33ab3d8de28f2b5bca429f91140e2c7a9b5ae9fb85b6ea9b46b9b3c796fe040768f76ec0fafb1f9505df4ebdb3d4edd6e74db98ee216fe68ce47d280648f75e2485a44da385ddc13f4a025ddbdbea16a633286566ce55f9c8f6c502ad750db2c514f30dec428247e6340bbf04100b73402afb943ed2b9e30683836defe9403bc1e06734020e06280cafe8683a375941d841c77c1a0151b467b50159f00e4127e5402872371040c5046eb5aadbe9b1c02e2f6dad25b89047099c677b7b0140fe3f1010afc803f3018e68160c3041ee2823f5dba92d34db89a1d9e2843b03b6d05bd013560c1748d57aa2797c6b35bab78e6959dc47231580ff336dcfb03c1a58364b5bbb7d7fa7b7427f1f673830c8664285bd1815238fad20f2c7c41e979ba43aa2e2c1cb1b663bede438f3a13c7dc76fb5515e9065b851f7a02950002a09c51a1b83cf14176e90d3645e9ad7752752aac23b3439c066665c827e944d29a6410aea725c4567135bd840d3c88a723728c29c9efe6c50d3ee9545b0bf8ef2e6e3c2fc2c6f72f2920e5f19039ee4938a9a875d03278377acf52ddf867f036ef71923932bfe51fbd3475cdc369df0db4fb389d4ea37970fa9cc0b00511795ce7d4f181eb4cd2451755fc45ac16d637381b14ca36b641dfce723e4053170d6cb52bbb362f6d3cb19241f2b9029862f09f143549ba7e7d2eef6caf2797c66ee17fdfd69862d1a069da7dfdac579d17adcda5ea9e1a992376c4723e39e3b024fd7e94c458ac3e25dee8d31d3bae74e7b79002bf8b8549471db38f5f4ed4c165e943a06a328d4ba605b4b22a1523c420c64fbaf38a82d36f0ce7cf7463790729b53017e940e0b0ceceed8ce0500e1b70daa08f5c9ed41d271cd0132476e7d7ff00aa069797d2411168ed9a41fcc858211f73c5075acb25ca6fb82aa31e58a36c81f561dcd033d42169e158ac64b98151b3981c2966cf639f4a064c7a8ac55e4865b7d493701e1c8e52403ea3cbfda827e390ca3f2c914aa81991bd281cdacc2747215c60e0ee5c67e940cb51b0b2bcbd824bfb08ee1a252d1caea1821cfa67b1fa504982b2283ce08f518a08abb82f6dd0369a5662081e14ce40c7ae1b04fda82275cb0bfd4f4536f7114589a5412461f3e4ce4e0e060f63f6ab2893d3b4b5b5b78e22ed22aae3cc3cc7e64fad3449a22a461500007602a0cd7e3b74c26b5d2ad79147baf34eccca40e4a7f30ff3f6aba3cd0543267eb5427b86f1f4c76ef45d0eca1ad5ef224d13e1cf4fd9b22192fa67bc955f8c8c617fba9fb510d7a6ed3fd43a735e5b54964be658c048fb6cdd9e7eb8a186bac97d174e6d22e23437b7ac26b95e77c68bf950fa7279e2b22dba45b59e97a669fa4ea36aeff89cea9a90451fc355ff0096ad9f4ce3f41570675d4fa8c77da8de5cde5be26bc653171ca47dc1f6c9fed5562b97f70276808da7c24f0c1c63804e33fa8a2928c0e0383c8f7ed41d92a41393f4a2548595c2c37493db4cd04e8a08f139566edfef3445b6e7aeaf65d2df48ea2b11776ae02a93e564c772adef409f4ee8ba9a21d73a36fa579ad9f325afe599171ed9c30a960d5ba0fe2843abb47a6f510fc26a4c36890f9558fcc6783506a1147b510024e30339ce680d2c6ae9861eb9a009178a0205443b989e39cd01d8075e3047ce80563057ca381ed4011c4531e503d85013c91b804a21279c903341131cda8c3abdc8650f6d20c4321232adec3dc504bab2c113c9293bb1963df3408dd4b75e1efb2856463dbc43b4631fad047e9177ad4fe32ea16b1db4b8fe1aa92571f5f5a0916bc8e0895af5c46c17cd8c9ff7da80f6d736f7f6915c59cab35bc837238ed8a072a31c1ef4062870718a06f7702dc5b3c522ee4752ae0fa8230683c75d6ba3b74ef535fe984929149e4278ca9e47edfdab42058003763ed409f88ffd6dfad06b1f12ae612fa0c76e0b471e9916d23f973eb4158d3efeff004a984da5debc1295d8e4018dbf3145d583a2ad96f356bbd7f5d90dc59587f1e79a6392f28fcaa3ee47159444ea3aa5ddfc7acf50dcdc344d7a4dbc317f52641200f6000fdeb41b5ef51d8eab672ffa9e971c97c11638268e431a46000012a3b9a351567db823b11f3ef40948e428048207a8340ab48ae83cb83ee0f3428a982719edf3e68c9cc97d3fe15ad8c9be138f2bf38e7b8f6ef40f7a5f55bdd3f56b46d3649127f1405f08e7249c76f5fa50689d48ba5f545cdcbdb462cba9206411b2b055bb07d4fb1c73528d4fa8f52d62cf47b6b8d2e65fc458c49f8a818795c151939f977a823ba0fe253750eb7fe937b04293f9f6c90be41dbdc7ff006283473c1efc1a06f69776d73bbf0f2aca32572bc80470450284a46dfca19f819f5a04e799614def26c0bdce09cfd85045dc75769d12dc3c3e2491db0dd3c85195235f7c91cfd066ae0cdba9be31f4ec61a386c1ef9d4ee473e45cfb1cf34c101d3ff1ac9d481d46c628ed24751881880833f988e7b0fa5328dfed2f2def2ce2b9b79925b791772ca87208f7a60182ee2b95cc0c48f53823fbd40ac658b30f4f4a086d4ee1d75bb6b78f4e965596366fc5211b23238008fde81f43692da5bc30d97831a0397dc09e3d714087506bf61a2c4cd77324726d2caaec141f9fd2ae0c435bf8c57173ad7876f7a2daca10489121244cdf319ce3dbf5a834fe81f881a6f57bcb6ba7c53c72c11873e28cee1db391dbef4199ff00ea4348116a5a66a8a8a04aad04847a90723f6ad7d18c312ddc02a3815423ba0f63fa541687bd9efe1b533b3c9e0a78473e899e318a09bd0ba6eef543e3b2bd8e9b10064bd9e4da001dc81401aeeb29a984d0ba7d5e1d06d4e6594f06523bc8e7f5c0ac8af752dfc17d7090d9218ec6d9447129ee71fcc4fb9cd6842ab10dc0014f3e5a2c1704b671dfdc734525226dc939e283a362c7f940344a380393df144733e2276e38f5efcd01b4bbbfc3dda4a9298a44395902e4a9c70682660d4265d62de40b1bdc1545054f95c8fe627df141af7c3af8808f3dd68dd5d2a45765884b8908d8c3b6c27b7a77a945d7a5fa474bd2ba8e4d5748b28624955d5d8b13b79ee9e983d8d40a753758c7a46b96f6114725dc92279a2810b3a64f94900763cfafa503fd3b59b79ed84da34713c0cd890f0a158fa1f981de826e1b548959fc4dc5cee24b6467e59ed4101ff19e9f676baa5d6a72c50adb4ad1ac790ccc076200f7ad41e7df881d79a87576a5f87b0f161d381db1c2a36e7e6d8ff3416bf87ff082c6f208ef7a82f22b9761bd6d619785f6dc477fa53705ab57f83bd297ceb1e9caf67708db9c4526723e849e3e94f212dd25d117fd29a8c09a76b534fa39cf8b6b71ced38e36fb73417f52e64548e34007e673e9f21ef590a1c918c90718dc281a69b68f67118d9da5058b798f6fa7fe280daadd1b2d36eae70710c4d263df0a4d583cc7a668fd4bf11b5837d7c93dcd9a3146959822a0e781f4cfa55161e9dd7fa67a4f55b9e9aea3e9f81fc09ca0ba118998fcdb2338c7b528d39f4cd2ba76e2d357d292df4eb391809963420ce1b1b576fa1e7359119f1eb4e17dd033ca172d6b2a4df303383fdeb5c8f2eef3bce4e0e335684cb0c9f354160d36f64b0baf16072b91b5f03391f43c51aab23a5debe91c4fad4d73689e6fc3a290573ff4f03e59f4a3280d67581ce916567f84b58ce0a1fccec3d58fa9a084de08c90464e4d1a8e419059b201f4a05630a176918efc50176293872c17bf14042aa0125b03db14046c60b60123fde6827fa0c68edd5365ff11346ba6292ee64194240c807e59a32b7fc51bfe8bd5ed5db424860beb62b89218422ce09c11c01dbbd0660ae110bf1bf2154838dbebfefeb41a8f4cdac7f117458f4d9ecd2df53b4cf81a822808c47255c0f7c8e7fb54a2ec2cfabba3b4b4b8d3af12eedad40926b0f070a13f9b633649f7a82eba6ea4357d321d4ecad512daf20df26e016507fa4fbfaf3e98f9d067dd2bd2faac9aa4d72d72d1e9510ca46a7631c7a320e18f1dfd7bd059afb7da816d23de4ba5de211346a1e4785f190548e4648c63b64e6b43ce9d5baafe3b539c5b452dbda46c638a167cb281c73ee4ff9340e3a3fa5f5aea4ba58f4bb57dbfcf2b02a8bf7f7a0de3a5fa0b50d2a2d92eb3e048c0a97c867dbedcf6a944e5cf4f6b76d1b3d8ea42795066266c87c81c65b9cfaf15048e83af3cd64abac08edaf01546c38dae4e0657ee6826e5b892de3702292e2545ddb55700fd0fbfca81c4b3bc718716eef9eeaa402280d14ab3c0b2c65c06fe571823ed40df56b217fa6dd5ab9216689a33f2c8c558307e83b8d77a37aaa7d22f2512c28768800c9954671b3d33ebef568d0ef7a7749eb0b5bbbb162d657b32b46d2e1564c8ed9c5644d1b0b9bbd261d2a440af6cb0e2e5b1e7dbc1238e0f7a0375b696daa7496a3a4dac8a92cf078685b271db04d391e40d5ec4586a1716de2a49e0c8c85d3b120f715ba1899173ff305413070abd89cfe9f5a2d3ee9c8639fa874eb6b804c52dc46b20c9f302c3bd11e84d47e1af4d5dc6521d3e3b662c19a58721ff5a9a321f89bd27a374b456d158dccd34d333332c9b4b2afbe47a7cb1f7aa33d2bc0d8c0f1c8f6a2c14b6d501b39cf63450897380c319e3de8065031c038f7ed40d8faf1ce41e4d004876a8dc3cc7e743025c956c818028c904579e7f0e15695c9c0541924f6c00283d0bf07f42d6b48820b8d62d20b2b58d656404959e52f83c8ff00fcfafbd4a35bb06f12391a48dd55cee2b2f3818ed8f6a8158a159890f02242079147623e631c502b0db436d1ecb7458d4738038fb0a087d6eeb508f48bb7d32d95750752b6c26c905b3ddb6f61eb574794f5cb6b9d0fa9678b512b25d24bbe52b8c1638278fbd582c57ff12afaed45b5bc0d0d8a8c08a2731ee3eec5793f40450466a1d59af446293c186cd53ca0c36eab93dc649e49fbd048e89f1675ed35e301e293919dcbf9867b37cbe94a35fe94ea4d33aba6824306dc48015750d86c6e247b0cf63591a40b8dc23fc30f14138dcac3000f9d03687547f12e8dd5af816b13148dddbcd29039c0f6f6f7a0eb5d62caf5636825db70c9bc4328f0dc0271c8a090627d3073ce681acf6505ccf14d35bc2f2c2731bb28254fb8a075144a83ca806792400334049ee6281e2496408656d880ff0031f61fa50446bd76058ea1b9e21025a3bb48afe71df9c7b71de9c8f196a0de23ca7b827d4f7add117e0cbfd4b5059392369663ff004e71c51aa97e8f555eadd258f2bf8a889cff00dc28cbd0bf123a926e96d163bdb74490bca2321c678209ff001591e71eafd7a7d7ef45cde2c20aae144638033fb9ad2e1b5e69d058da431ccf21d4a5c3b4631b62523807feaf5c7a50222f2d648c25f5aeec8c2cd19dae3d3e87e944d3eb7e90d425b49ef2292de38224f1505c3f8724a9eeaa7bd0d57a60406059436306868a7803839c7ad1a158039c13f4a33a716767f8cb9b6b55e1ae2458813e9938cd07a9f42d0b4de99b4b7d1f41b58ff19b03c93ba06607fa8b1f5f619a5b8266d74a65d42da6ba90cce996dcdc8c9fff006a5a2c2635083b05ef83eb5028076341db4b1ed9f7a04651fc41db18ed419d75b744dbea335fcb0db0335f2057901c05da73c8f9d5d18a75174a3f4c47335e35da4ce418a489374254f707d463d33565d1529b569a489a17944b06ec8057d71dcd037b4b6b8bfba31584124b27e62a8a4f1ea68357f83da7ea5a76bfe0912453ccabb49194653cb60f6ce3dfda983d196cd108c2401711f9768e306b2297d73fc6d02773a8b591922693c5004bb9d72542fa2f6efde8314ff867aeeec27500b77bb5670e36ca19b1dff2e7f2fd2837ce8bd5dd348b78b552219022870d9c46e792a4f6c608a0b846c8e03232b29ec41cd0199f1410fd4b24b1e8f712c0a5e4452d851e6c639dbf3238a0afa42ba77475e4ba8470896681da45180b18da76af3c9029c8f26dc1df2b9c606e273e86b743331924f27f4a82c12280e59b008e79f6a2d4d74188ff00e30d203a82ad7519c1ff00b860d11ba7c5e86c9fa3afae6f4091e043e021270b21e01c7dcd6479ab4dd3aeb56be4b7b184cf2b301b57d07bfd2b4bad0fe25e9f6960ba7c7a55ac50cd750335ccaade7723b83b8f6e38a2207a5ba4e7ea3d93780cb616ca53781f99fbff009a0b675a5be9765d43a75a6ad3b25adb4185429b831c70303dfdfd2831eb8954ca48f3827819c71ed406b2b1b9bf9a5fc1c4ce2253238047957dc9345d122b792eee522811a495ce1157b93ed444ff0049f476b1aaf51c761345269d25be269259570c833c6077249e062a68f53e8ef0da69509d4ae225b92a04af232ab16f98cf1f4a5a266d4dbca8af13a329ecca723f51502d14f0cb9f05d1c8ee01c91f6a0393b4edfe63c8a031608859b38f97340d84d04e5846eae50f9829ce3eb400fb24466041f5e3d2823f56d22db57b192d6e61468a41c823ff0035651916bbf04ada7badda5cad6d1b72c09dc33f2a6875d25f0865d06fe2bc6d4c4d3282026cca8cfafcfd29a34cd234a10c768f711a78f1bb392a3001208e3ec69a26a58d640c832091c90706a084ea1d3eeafdadf4f86da3166c0b4b397c18f046140f5ce4d04f4702436e91c28a9122e028ed8a0a9f5a5b6a09a1bc5a135bc72cce048b3c5bc15c638f9d59043fc2db997481aa69dae49e1cb6bb643239211939e467818f97bd305965ebce9a10bc8da9dbaa2679dd9ce3d8530572cfac87566ab05ae9f1490692b9696e1f833738555f96793504df5f25945d2576b7ec16dc46792381c7b7ad5e60f234980e42f6c9c56a82ec3eff00bd4124e49700f1c646e3cd169ce9575f83d52cee324347323f6e3861ff008a23d47d4ba6a75074fdcd8ef317e2e2ff0098bdd4706a60c3f4ae8cd5f44eb8fc3e97248a638cbc73bf90483d463b373e9574685abf42a6b5649fea72bbdeac4a8d3b018cfae31f7a6895b6b29b41d30d8e9f6bbed9213e1b7a994e724fcbb5064bd7835a9752d3af75d8116354778f660788cbd9483dbb0a0cd20b2b8d43528ad2088bdcccf854039cff00e2827a0d34e9da1de896f2182492efc0976f998aa827d3d334113a74aa9a9298628e74570478bc0c7cf1da83724bb8246d3e6416b0384da61b5501c9f5c3704f152c037561a95f5fce61d3ad6db4ab950f34b331dd9f4191db8fdcd406d67a675ab4b6d325d1af248272a43430315ddec7038f6ad4b3f448bf47eb71cb69abddebf21d5e26896203846c30c8603b9c6452d9835901405660376319ac84bf13180779d8bb82827d4fb0a06f777367a75acd7170f1430a9f331200cfceae061a0cf6dac692d7365266191db0578f5edf3a6075a6c9278b3433188a467860d96fbd40fe540471409aa0c1140750001ed8ed4058e15133c983960077edf6a06faade5c5b7822d2d926766cb967da2341dd8f0727d85033d27597d62e2ee3163756915bbf8799d71e2f19dcbf2a092b88dd9a311950a0e5b70ce47fe6ac18af53f5b69da9752dd69da9ca906876e24465d9e69881c6ff005c679c0aa2bfd267a347512c93dbb5d42d90d3c800b68c9ce0ec3cfa528db74ad034db5905ee8be1ac728dc153984f3f980f4fb56453be2de8f647a6aff53796596f0aed46798ec033ce149c0fb0ad71479c9bb9dc3bf3c55a0b95f65a825150b481a407b93c0fda8a29c06671dc93803bd131eafd0af6dffe18d2ee25982a4b04603b7a9c631fad03bbe586381bc5945b96385718c827db3eb5288eb8ba934eb15fc3c535f05427796dcccdec7150637d5bd55d5362b7975aa4d0d919018adec8637807bb60723000e4f7cd58203538aefa8aeb478a7b9beba924547b8774cf8608036a80704639cf1f9855d1a7f4c68b67a03de5e5d59dad8d988c62e1c0f107a1e7fdf7a082ea6d07a6e3e99375a7cb6b3db093c727701e2360f7f53dfb50653d4130d42ee18f48b3f0232a15218936963ebf5fbd06dbf0cfa74855b9d46e04b730c6144691e12307d33ea7de8348ba6b5478a279a004f98c479247b81f5a9438805ac0be2e02e73c9ef8fbd40c2346d43578eefc40da7da1dc8b8eefea4fcb9fef419beabf12a4bcebcb2d2fa7ee0dc58492084b30236bb6467dce383f6a0b87556a67a7f4d95a0bbb5468816f0a69c78b2e072572719ce78357079dfab3af2e7a92c963b88d94abbbf91cedc93edf418aa2c5f0dbe2a6a9a0c90d8de34773a6a8da1186d6403fa48fec682d9adeb7a9b4c9d572dacc9a6c9700456e5ca910e000ecbd8e580352fb1ae7476bd6dd49a325e5a9f3025245fe961dea097523cc0919a032af039a006936c81423104649c703ef40dcce64bc3035a87b6f0c378f9fe7cf2b8fdf340a4b6e25962915d94a67807839f7a043586922b5636ec44c061063f31f6ab079d7fe19b7eb2d4efeef55d5d74f992e9a0fc3a441dcb13927b838c9aa2d4bf042c618e178efee6e18104870172318edf5c1e6945bbe1a748ea7d2315edbea3a99bcb190030c401010e4e783ee0fa56455be3d6b90c1a6268d69e17f1486900ee98ec29ccc183119419e7e55ba11f089f523ef5058363a8059fb8e31e9421b491056c01819e28d3d0ff07eea3d53a1e3b6b8db235aca63c139c0eea68ca47a9fa6ef757b83ff00bf68ad428c2f248c7a8f9fcea518df516adac74e7544f63a2ea172f1800291e6cee19ec78cd5826344e85b6bad25ba8fade5b99dae0ee11efc71e858f7e7d054a2d7d39a75ae8f7b6b00b8917f1516624b78429da327cec493db1db1d8540cf4aea28f58d6aeae2f6dd64b498082d880488d149fcea7d4939ab04175e6850a8d32de3b78e380c8de32c4db4e18e430fef543cf86fd0d691b4fabdf6648b3b2db69ce7dd87be68342d2f4fb9b5b891af1a28a2dc05bc5036d001e0eef7352884b961a2ea9aa7555c885e08d45b5bc52b61b686c120fb939fb541276bd4b61d53624d942e2f6200bc32290633e99f4233416dd3ad3f0d611c0c77b632e71dc9ef41156dd27a45addcb3dbd9c513b1dd941821bdc7b558333b9f873757fd69a85e3f813e9c7723b5d93265d872473c11544a68ff08fa75e290b42ec4e4124e70738fa5048e89f0f745d2aeadd2decedda6525c975121183c77f7a945c754d0e0d563682ed43425369403bff00bcd58308ba7d5fe13f5a05889974a9d8b46aede4914f707d88ff001528ddf4fd7edb54d1a1d56c312dab2e64dbc9418e78f5c541296d70b716d1cd6f8789977230ecc280cb7519b816f212b205de4e0843ce300f6cfcb39a0545c42cee88e0b458ddec33ee680eac92266360debc7b5056fad2d354b9b189745744be121daf27e550548ce3d4d58324d07a725e98ea2b7ff5381f5169a7579d021fe13904ee43ddfbe49038ab46e76cf05cc714f6d309232a4a98ce54fd6b2196bb7f2e9b631b2c427b891b6851db3eff002007341e5bf887aa2ea3d4f77378be381e42fdb711ed5a1554395caf1cd07617dcd04fc85402101da791421b49920331381c60d1a69bf02f56f03a925b12c162b98c955f775e47df19a32d99b518268e4491668704a79d4aeec7b7bd4a30feb7e9144d76e265697c3e2693631674273803e556087d76f35fd49859e9925ccf611141106f2e182e3241f727f5a94681a268f79ad1b1b8b9dd66b1c2b1ce9bb06361c1e7bf3fe6a096b0d3ba57488e485b52b40909c386901607d47bf7a0ae758eb69ac4d15be81a748f0a9c35cc90b2eff4c03c1c638a0b77405c5d5d45f87be5fe359a88b81b401dc1c7d38fb50586fed18ea3015790091591e447c1518c8c7a0a0a5754d8c9d49a8d9f4ee9dba0b3b5224b9692327728f627e7c6682f9a7e996b6b3a8b6b748a348820c7720761412c064e3041ce282b5d4bd73d3bd3f33daea97ac2e540dd0a292dc8cd043c1f15ba2a7923b65bb910371b9a12141f9d02edf13ba2ade56857551e5e77244c54fd0e280746ebfe99bbbd655d56dcdc9ce08465565f4ee3bfca82d53eb3a6dac3e25c5f5ba646402e33fa77a0aff5b74ad8757e9ca972844aa37c520fcca7d3f5ab067bd369a8f467544d626c98e9f7118f0200e4465c903049c8c9e6ad1b24334b6fa6249716cab20037c309dd83db03b5640dddac3764a4f02cb1103863919fa7a1a06d6f600c37162911b7b252b87dc773f1927393f4a079f868edae1ae6328a8b1ed38e30050226e85d5dc1f879011b3c47c2f604719f9d01eff4f4b83e3c6b18bb452b1cac9b8a83de80b16e8208a3b7b58e1407cc061427cc0ff1560ce7a8f592d69a97504cad2dac01a2b53900c3e9e51ea58f727d0551e73bfb86b99a49a46dcf21c96340dc13804f20f6f9501c0e3b8a0963316fcc4607007f57bd084d64dec01200ce483468ff0040d525d1755b4d4206ff0095207c11dc67ff0019a18f56584f6daad9dade4211e39104a8ded9152b235cd8c530613229c8c1c8ef50472e81690ee00322b0c100f0debdbb7ca8111ace856371358cba85aa5cc407891ccf83f2ef4048b4ad2e59bf116769672c72f99dd1437239078e2824a4d3e1b94559234110e781839fa0a0561b38ad532a12319c86c6307e740a9732a3a00cac870cd8e0faf0681be8b6db965bb909df3c85806eeabced5a09523647e6e0fef419a6adf116daf7ac34be9dd1da686e7f1ca2e243b76320ce57df9ff1560cc3e3f470ff00c78255b842b35bc6c4af9b6e323d3e95467b6365f8dbcf062beb68c119595d8aaff6e282422e9899b4f6bb5d46cda2562a76316c1078f4a0859e1b9b762c0bf94f0e84feb4125a57505c58ea70dd5d0174a986d92b1c13f6f5a0de7a5be366877260b5d42dee2d2423124a487507ebdf15289dd3fac7a7bab6feded74d61733473acdb5a162142ff00313d81ed505fa58fc6d809380c1b9f5c502e0e05040ea367a85dea454de2ff00a610375b04c16c7a16ef8340b5f6930dce9375636acf6a278f04c5dd4f1dbf4a084e91d06f3a52dee62bbd4a2b882494ced3c8a448063b63b638fde803ab7ae749b2b3096d792c93c8c109b55dcd18ce3710473ffdd043dc758dc5869044565aa5dda4c3c2b7bc78c1f14e3963db03e7c0ab066bf1327d41ba76ca6bc48ecad24c456f6b0c87cf8e4bbfa138c0fa9aa3297c83dd4e28395811cf2680a5b93c7ed413cd1ff0f3c797b8031406645236b0508406f30e68ba49c051b97d0e0e7d28ad57e19f575c5be8f269515dac772877c11bc464dea7ba8c739ce78f9d3193bb8ebfea2bcbd6b5b6b8b58bb7f13c2f0ce31cf0deb4c0f2dbad6d743d2ee99efae752d6c02a86e0054524f6383c7ff94c0b6af274c75149a46a5a82c46f1e1479fc3190bd8156fbe7f4a960bf74e9d253f1167a3ac09e0856610e3041ec7f6c540f67b892cee7f8d18368232ef2af2508c7047cf340ead5bf130accc9b1186541e723d09ffc5033bbb1b82d74d6b37f1244daa1b38073df3f4a08eeb1d3b50d4fa6a5b4d32f12cef1902ee73e523d476fde8306eb0d3fabfa4ba92c278af67bb7281606472f90bdd58558253a6afb40ea1d62283a8b461a66a6f931cf6a7c2466f7cfb939e7b5515fbed3747b5eb8f06eb78d35080a2ec9719c76f98049a0b4ebdd37d1bad869acbf0b03c5c16b29444adf50ded41995f68564a263a66b31cd02be152505493f51c1a088bab69ad1bc179e320f07c37c8a0692b46c4995f0381db39a0b2fc34e971d57d4705bc8db6c50ef9dd97b81fcbf7381528f5ae97a1d8e996d1db69b0c7648855b10a81b80f43c739c54134147b9a036063279fb5046e957726a0f2cfe04915b06db1788305ffeac7a0a00d72f8d9c491c06337533050ac7185cf2df6a06da2da4293488f34973328c34aea428c9ec3eded40ee7d2ad249448f6b133820ee2833df3fde819ea96897461b05b87815f2ee919e5d47704fa039ab079b3e326b70eafd4ef6d6650d8e9ebf868b69c8247723efebf2aa280eb9193ebedc5002a124e015340018fb8fde82cf32b1603d0678cd02406dce3008e47ce81b499c331383c9c9f5a2e9c69377369f7d6f796a4acf148acb83fb511e91b3b3d0bab745b7d45acedd8e3732b71b1fd73f7a5a19eafd09a56a0a96b1c705b49c48510761ce4fcfbd4d0d752826b2b583476fc3daacb295b79d768de8a32b1e71f989e49f6a7d14dd1af5ba275a45b8b093c054492ea769092373765c1da4679fbd306e36ba9595fe9f0dcdbcc92c33e1579cf27d0d409ea178f68521b6b76926ee8a7853f7ff140bc768d78f6f73748d1cd103b543f0091cf6efc502f7319dac194371d8b6326829f0c501d7ae6fa568d5d4942c806d4db81839f53c8cd59456fae6e628749b5bab8b1865b08e4726588ec11e7f2e49071c93da9a31dd4341d675e9a5bad374f9858162d0b4ac70e18f0573df35a0c759f87bd53a404f174f965dfff00f479b1ef570576e34bd4b4cc0bdb3b9b7258a00e846e3f2a94376475cee4914af7ca9150685f09ba61efb52fc7dd69bf8eb7c158d1d0b47bb38f37efde968d6eeb4eb5e91d6ad25b660aee59974db6881690918e31ce39279e062a5a34bb57b88adedd1e379679065d80036679e6a07e8391bce7e940c659ef5afe1286de3b16f2b8903094b7b2fa7ce81eb380c4260ed193f2a0cd6fa5d4a4ea0fc7bdadcce923158a3039db83c038e3ef41a0e96b2ad8a35e009291b8a939d9f227e43bd590436bbd6fa269202c974b7123602c76e779624e00e29833bf897d493e896525dbcb2a6b5a9c3e1456b91b6d60cf989c7f31f7a60c02490961ebcf3eb541308e39e067b507007b96007a67fb50178f97eb4165ce18165c2927b773fad023202d9c8dbb7818ff003408300b87f2f1c107d0d0c15a4f2e339c90467f6a18bdfc2cea8ff4bd561b4b9ba686d6e64552c4f954e7d7e46a60f4688d240af1b2bc6cbf5047ca960617ba658de1b792f2d94a5ab33461b18524633fa1a81b5c8b5168967369d23c0e0a24622dc981d81c76aba29df0bb48d660d52fceb88d069f04aeb69130037127f37b9c0ed9a8350781240bbc06da72323b1f7a0eb8816e633192ebc8c9472a78fa50349b4c83c068e24f0ddbcc1c13b837be4d055b57e98b996d4db5b4a893dc1e6620b6ccf2c467efc504ce97a38d3f4d874bf09af6d46e2f25cb82724e791db15650a43f878b51fc34f3da8f132b6d6a98c80a39ff007e99aba249631b58b9047239ec3e55368aeeb7d2da6f52c0eb7f16e87f2c6e836ba90724ab7a67b55d115ac7c3e8aed2182def4c56a14096368959a423d77e3229a27b41e9d8343b01069c8a8dc9660aa3713df3c64d4a1c695d3d6b67a8cba94b9b8d4e61869e4e4a8c636a7f4afcaa09a485519caae19b966f7a0435196582c656b74df3e308beec7b50629375775b691ac5bdb6b16d6378779f019b00a31cf391c9c2f1daae0b35ef52f5374de88d77aa45a6cd25ddc0108694ee2188c28007603d6a0d16c92430a4b2ed3230dc401855cfa0a0a07c45d7b5db9d462e9ee960b14b2ee134ef8c850012147ec78ab0670b643a2efae753d72686e6e2da211db42176079c8e768f65e39f7aa332d6f58bbd635096f6fe6692695b24f603d801e82823cb900ee00e68006460051dfd680ed9f0c905b713d8d006d5f5419fa505a18f94e40501b1b81a04186d62402c87be3d6810b81290aea8467201231cd1749dbc437f9f1e201db3de8ba07dc0175c027f28a335b17c26f888d6b6d0e8fabf892a29c453b1e547f49f7a946d6424f08236491c833ee0835073294888894120700f0280813c40a6711bc8843e00fca7d3ef40e41dc081f9a811681c6f7565329185623b7e9de812b3bcf11ff0b74563bd50494cf120071b97e5fda80d7577046c9019d5669dbc340324eec67fb734103d5da96bf67a7cf0e916f6e2765f25ddc4c11107ab1c8c647cce2816d3ec7f0f6564cae6e67da375e6d52cc4af2e4fb13ed4145f899d47b3499f4bb6d46cda49b69b92921565c3648e3dd40c81cd5c0ae89f13ec246d3e379ed2d6da180b5d34849da1780b128e49271c9f4a60ba685d5fa36bc42d95c324ec7090cc9b1d87b81ed50588958977cacaaa3b9341c655f12348d1dcb8dc1946540f99a019e2134454eeda7bed3839cd052fe2136b536b5d3563a1ca53c49da4b9507198940ce7e5c9fbe281c6b7a974cf4ee4ea7242d76dc784a3c595b3e9b464e3f6ad0ac745ccbd4fadcbabea42da56959a382ce7460d6b1a93c01f97272093ebf6a82f1ad6af0e9da5cb3cecf6902216919f82aa3818c7a9f4c530649a9f5269ba7429d472239bc991a1b0d3c3152880f0f23039e7bf3de90635ab6a377aa5ebdcdecef2c9239e59f3827e5ed54302195fcc38cd01245395c1f5f4a05b606538e483c501b6939e3b5077860f3914165754c33e549000dbe87de813b820c27fa7baafb8a04a69c98e281e42618c795338033df1f3a06c03e4e029247007ad010093c35674da71f977640340081a190658e41c820f141b0fc33f8926c218b4ed609366a02249bb2d19ce3ea4528dbece68eead926b7916689c643a9e0d643387521fea2f693c2d6efc786ee46d9bfed3eff2a04669edf5295ff057a60bd865309246d3bbbedc1efef41d63a8dec9ab4fa7dd4510fc3c69234ca186e2d9c003b7a67bd034bad0a5bb96e25d575267889cc1b54446d9bd0a37bfbfbd02925945a72cba8dddc48b3f87b1e58f23c623f292bdb7fa7cf38a0a5750f54ebba56a9a67fc516b6d6fd3970ea9234677c8dc7f38f6e4640ce282d1ac4b16bfa72c1d2bad430cd1ba822061865f5007d3daac19cf547c189357d561bbd3eee683c62cd786e9b73337b8c7bd512bd39f06adedec2de0d5ae639da372e6485363107f97767b505cee755d03a5e58ac228659af123184b7b733322e38c91dbf5a943ab3d52e64b49ee755d2e64950e238e35f10c884e17cbe87dc540e6d7509a4f110e9f7566a471712850abf6ce463e6280bacea36fd33a4497f773cf32c698dcc4beee33938edc7ad05534aea683ae61d64c4d2a69b6b88d16d5ca5c303f3e386cf61db140e27b5e99e96b64bdd562b6b30aa36c6c37cac7dc9eec6b42c1a66a962fa70beb6b516d0cbe76322f86c78f6c66831bf8b5d5d2dfa35a5dce60b1933b6ce3c788769f2b331ec1b8fd2831b79649984b239773c1dc68129725c1c640e73400ec781d8fb1a03c4a85d0c8582640257bd01e51fc42236263c9c67be280429c6037eb405dbf5fd682c2a0bb976cf07d3fc5009279ef8ec4e68193a9902b28e7dc71fb501d95b098e0f6dd9e0d0049131019b047b8390281bb292484e47c8500c4f242c3076bf704704739a0be7c3febfbae9a5daf23cd017c7e19fb107bb67d0f6fd6837cd2757d1fab34f4f05e37dde630b1c3a91edf4f7159103d6eb7da65fdbdf59dadb5e2460ac876ed9e1c8c060f9efe9c8a0a75cfc42d5742d2ee5a7e9dbb494b6d6b9bc930cce4f940e3cd81ed4160e98f88315e689fff0022b57664199cc5196f0c7a164ef8f98cd0589baffa68590985eb15c0db1985839f6c2919340b69d03f5285bdd6f4bf021424db4329cb153fccc3d09c76a090d3340d2f479a7bab3b38e2924e5e451cfd280d7dafe936f6c5e4bd89813b02a36589ce318a0358dc35cc4e17f9bf234cdbb78fa0c607a7340e6cec20b1596610c6934b8323226379edda81da8dcb9ec40a042f50b5bb21645473b58b11dbd7bfca8304f8add5d67a9ea8ba5d8ea72c1a4d8a952f10f2c920e368cf71e99fad5833dd0754d6ed66bdb2e9a91a5babb2a310465a57c1ddc1038e7bd5171d3748b8d46ee1ff005298dc6a764c27d4eeaee7fe1c01795881c9e7804fe940dbe287c4b6d75a1b1d1c986d62277c91bf131f4c0f6fad0663737135d3b497124924871f98e7803007d2811dc5b83903dc0a0333f03be7de8122df2c9a05a11e5f51f7a05ce7071804fca8033e5da0734020b0183bb23e5416269577ed0e5323078ceeefdff6a03dbcd62914c2f629a47c622689800879e4fbd046f9d8a2a03e31385c0e73da8b83ca590947dcaead8208e73da8849b3e19ce704f7c5015586d006431f5cf61f3a04ee586ff002481c8fe6191408f0011eb8e30682774dea9bbb5784492ca6385832e1ca95e3d2834be9df8c312e2db5eb4375080337000f1303d18763591a469baef4d755989ec6f6dae5a23e20b599406dd8e080ddbed41272f4dd8caf1c86d163910f9595882a3d718a035edd695d3b6a926b57d0ac65b10b4e06eedd863bf141077fd7af2782bd3fa26a1a8891d57c630948c0279393dcd04cf5875258f4de9f0cb7b7b6d66d2b81ba752d85f5214724fed41036bd79d2fe319d7a8f4b9c81e58de2f04827b9ce09a07a3acecf54b790685ace8697606009e52c377b7f2e682b097d7d36acf0f55df5edbdc0977412468cb6ce3be10af3c63b9c8a0b0751f505be9690dd5d752436f62a3fe4c6448f3b7b0c64e38f615734651f107e3045ac42b67a7693018633b965bc1bc838ee173807bf7cd33065baaeb1a95f2c11dfcd2bc51fe48880aa3e8a062a8b059f595df4ae9a74de9e9ec499d43c97b1427c6e47e525bb63e4282ad3ea3712893c599dbc4259c1627713c927de81043950df97db1406da8411c92063be280230839627078e79a0390a71b5bb5003a8c1232338e4507025573e9fbd02a0e41dc0e680c3691cf714053bb34160895dc16f291d98d02322aa39f3e14707ffaa06f202a5bb0c7201f4a343aca51090497efdfbfce89840c8db8e46573923ff14410b00490d9f5c1a0425dd8ce4673e873cd0265e4dbe7041ed814009b8cbb8e5863bd07163b7716e0607b6698060b96b7b9478dc8643918247ee39a60b7e97f133a8b4e0c63d4ee597380923970a3ef4c0e13e25dfcfab457ba95bdbddb212016501867b9cfbfda982f907c74b282da34874a9048aa479c83838edc62982b7ac7c42d235cd67f15ac5b40c366418a2cb0c1c81e6f5e31db14c160d035de8cd4a3f18ea96562cc37359dfe9cac887fef039fd6b39446f56ea5d13a9dca4579a922496b1975b8d22dfc3566cf9557230703be715ac1431d4d2275325d7fae6b4f6f182a93ef1e32a9f41938f6a60afeb1a95c5fea53dccf772cf2c8c489240031f627e7565c0d67bbf160487c1801073bc0c31f91f953420f2bc8c7c52cc540032738a809905c0f4fa501940208e73df34028e703938a0577ae013f4a001300db4f03b71407461ce0502dca8c9c7dcf6a003fafcbdcd0070bc1e0fd734070db467b8a04cb9c9e68274b93bcb1daa40200ed4099765249ec476cf340849b8b264823bf34689ee009cb671df1409bc8e8b8e770e3ec68984d9c953cf97be2860b248caaebc107dc67f7a184c31232db88fd451031ce50e76039f5c8045026efb8f93279e0fd680b239504f0483d88ef409ee25bb90c79c0e050151c6e21b39ce783eb40adbcc2cefa17bdb61322387781c950e3dbdf9c8a066f28790b22e013db3dbef54726081e63c6460d34191b1bb0720f634060e7600412c781502409c8e3d7b500ed71dbef8ed40243f181c0a02e5d4e0fad006f644e4819e3b501f7e3049e7b501bc43b4e391da80558003392d40a23305e320d02e64cf998e1bf5a032b0c927b8e68049c8c8e71c6280377043118f4e680bbff00de0504ddbb3128371c1c64668024e59f3cd02521254e4fad1a2107e48fe6a6809ddb9e78a029e1463d05027ffc744a6c3857c7b1a205ff00e637fbf4a02b12b1794e39f4a02024e7249ed409924720906800005173fd7404989698ee39e4f7a04cf723d07a501fff0097ed406ffe36a018ff00281e99a037f4d0731f3bfd28007e53400ff99a810248c0cf140bc60123233cff008a0557f9beb4056eff007a07109243e79a03778b27bfbd02b128c27039a054001b818a06609de793da815006070283ffd9}\par} +{\pard \ql \f0 \sa180 \li0 \fi0 Here is a movie {\pict\jpegblip\picw20\pich22\picwgoal400\pichgoal440\bin ffd8ffe000104a46494600010101004800480000fffe0050546869732061727420697320696e20746865207075626c696320646f6d61696e2e204b6576696e204875676865732c206b6576696e68406569742e636f6d2c2053657074656d6265722031393935ffdb00430001010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101ffdb00430101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101ffc00011080016001403012200021101031101ffc4001a000100020301000000000000000000000000080905060a07ffc400231000010501000300010500000000000000060304050708020001090a11153976b7ffc400160101010100000000000000000000000000060800ffc400261101000102050109000000000000000000010200030405061121b33134365154717475b4ffda000c03010002110311003f00a90cf388f366a62aa720ed6ae07f96901f3831d973452b8cf36fe3570fc908e46d466433e5dd954f2e96992d9e498c7753faa44916e016ca91cc7d88b38fe60a5b97737defcbcc539c98d336a57f4fc2ca9a486bf07ab575ad9a3af4df221d8215e36df86c4504ff0024574551b3d687ee0575757b3ad64e311ee62bd94158d37e24198c43973099f1fc0c41614d950246513a081abf76cfe7061f6863281e6352fd1670949c148dd6dfb0d25f5b3689b1d5c965b0eacbf4e0932ad28e22ab9ae945633f4744bd3c8cee0a7fdf085b9000f449c5f7afa30b83e0b6fd7b0c8429c9467ff9715347c891e25fa24a205861aa715e6a09bd0488237dc2723414d9891381524e8ca7c0894664f835653631ab55ee7e3de433e4ff001b30949124e4c10c8b6ad0a479b3f9c937b2cf5bc0095ad600a0a41a0e9faee174a1c605e161c6c7a313539650b0113190f1a8368e60d5b24f30ff008ea7f0bf867fa6595feeb6978f1fe0f9c26177f4d63a51a9235184750e7d18811339cd000000c75f000e00380380ae390c350def826ed42ad051fa6f501c50f9b699c3b69cbeb76476d202bf3ac985b6e0e968be66572893e6a744540bd9722e5c87956848629bc2559306bd113e8653d3b6aff651dfad7a3ac8b02958cba02a93ccf525757039bae6cff090e1d90688e8aa233ee86a4c4a3e0586d6b2340522e47dcb7d0046d8a5acb05a123ee25d2b230b2ada6e2e2f9ede3c05202520ec2487b0d56562529d8b3393bca76adca4ec1bca508abb001babc007915d84fe3dd14e207e3c62f8379da2a3b861fb6629d28dba53b6ea388ebfed866bf6dfb553455e91ed547ae92e9445253a4fdf3efb4f8ebdfbe7d3c78f1ee0bb9e13e358e942a4ed49e22cff00eeb35fdd7ebfffd9} icon.\par} {\pard \qc \f0 \sa180 \li0 \fi0 \emdash\emdash\emdash\emdash\emdash\par} {\pard \ql \f0 \sa180 \li0 \fi0 \b \fs36 Footnotes\par} {\pard \ql \f0 \sa180 \li0 \fi0 Here is a footnote reference,{\super\chftn}{\*\footnote\chftn\~\plain\pard {\pard \ql \f0 \sa180 \li0 \fi0 Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document.\par} From a010b83a7542d1324bde3d248c24faae9e681dbd Mon Sep 17 00:00:00 2001 From: mb21 Date: Sun, 26 Jul 2015 18:30:47 +0200 Subject: [PATCH 12/14] Updated readers, writers and README for link attribute --- README | 13 ++----- src/Text/Pandoc/Readers/CommonMark.hs | 2 +- src/Text/Pandoc/Readers/DocBook.hs | 3 +- src/Text/Pandoc/Readers/Docx.hs | 4 +- src/Text/Pandoc/Readers/EPUB.hs | 12 +++--- src/Text/Pandoc/Readers/HTML.hs | 18 ++------- src/Text/Pandoc/Readers/RST.hs | 2 +- src/Text/Pandoc/Shared.hs | 4 +- src/Text/Pandoc/Writers/AsciiDoc.hs | 2 +- src/Text/Pandoc/Writers/CommonMark.hs | 2 +- src/Text/Pandoc/Writers/ConTeXt.hs | 9 ++--- src/Text/Pandoc/Writers/Custom.hs | 2 +- src/Text/Pandoc/Writers/Docbook.hs | 28 ++++++++------ src/Text/Pandoc/Writers/Docx.hs | 4 +- src/Text/Pandoc/Writers/DokuWiki.hs | 4 +- src/Text/Pandoc/Writers/EPUB.hs | 6 +-- src/Text/Pandoc/Writers/FB2.hs | 4 +- src/Text/Pandoc/Writers/HTML.hs | 23 ++++++------ src/Text/Pandoc/Writers/Haddock.hs | 6 +-- src/Text/Pandoc/Writers/ICML.hs | 2 +- src/Text/Pandoc/Writers/LaTeX.hs | 12 +++--- src/Text/Pandoc/Writers/Man.hs | 6 +-- src/Text/Pandoc/Writers/Markdown.hs | 49 ++++++++++++++----------- src/Text/Pandoc/Writers/MediaWiki.hs | 2 +- src/Text/Pandoc/Writers/OpenDocument.hs | 2 +- src/Text/Pandoc/Writers/Org.hs | 2 +- src/Text/Pandoc/Writers/RST.hs | 8 ++-- src/Text/Pandoc/Writers/RTF.hs | 2 +- src/Text/Pandoc/Writers/Texinfo.hs | 4 +- src/Text/Pandoc/Writers/Textile.hs | 10 +++-- 30 files changed, 122 insertions(+), 125 deletions(-) diff --git a/README b/README index 3bb211341..2536c74ae 100644 --- a/README +++ b/README @@ -2644,7 +2644,7 @@ nonbreaking space after the image: #### Extension: `common_link_attributes` #### -Attributes can be set on images: +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. @@ -2666,7 +2666,7 @@ and `%`. There must not be any spaces between the number and the unit. For example: ``` -![](file.jpg){width=50%} +![](file.jpg){ width=50% } ``` - Dimensions are converted to inches for output in page-based formats like @@ -2685,10 +2685,6 @@ For example: is to look at the image resolution and the dpi metadata embedded in the image file. -Note that while attributes are also parsed on links, pandoc's internal -document model provides nowhere to put them, so they are presently -just ignored. - Footnotes --------- @@ -2964,9 +2960,8 @@ letters are omitted. #### Extension: `link_attributes` #### Parses multimarkdown style key-value attributes on link -and image references. (Since pandoc's internal document model -provides nowhere to put these for links, they are presently just -ignored, but they work for images.) +and image references. This extension should not be confused with the +[`common_link_attributes`](#extension-common_link_attributes) extension. This is a reference ![image][ref] with multimarkdown attributes. diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs index 9112979ab..7f752c446 100644 --- a/src/Text/Pandoc/Readers/CommonMark.hs +++ b/src/Text/Pandoc/Readers/CommonMark.hs @@ -113,7 +113,7 @@ addInline (Node _ EMPH nodes) = addInline (Node _ STRONG nodes) = (Strong (addInlines 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) = (Image nullAttr (addInlines nodes) (unpack url, unpack title) :) addInline _ = id diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index cbd50c252..db438e26d 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -967,7 +967,8 @@ parseInline (Elem e) = Just h -> h _ -> ('#' : attrValue "linkend" e) 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 href "" attr ils' "foreignphrase" -> emph <$> innerInlines "emphasis" -> case attrValue "role" e of "bold" -> strong <$> innerInlines diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index 67a97ae85..b80280553 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -533,10 +533,10 @@ bodyPartToBlocks (OMathPara e) = do -- replace targets with generated anchors. rewriteLink' :: Inline -> DocxContext Inline -rewriteLink' l@(Link ils ('#':target, title)) = do +rewriteLink' l@(Link attr ils ('#':target, title)) = do anchorMap <- gets docxAnchorMap return $ case M.lookup target anchorMap of - Just newTarget -> (Link ils ('#':newTarget, title)) + Just newTarget -> (Link attr ils ('#':newTarget, title)) Nothing -> l rewriteLink' il = return il diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs index 04edf4c6a..fb86f1286 100644 --- a/src/Text/Pandoc/Readers/EPUB.hs +++ b/src/Text/Pandoc/Readers/EPUB.hs @@ -192,20 +192,20 @@ fixInlineIRs s (Span as v) = Span (fixAttrs s as) v fixInlineIRs s (Code as code) = Code (fixAttrs s as) code -fixInlineIRs s (Link t ('#':url, tit)) = - Link t (addHash s url, tit) +fixInlineIRs s (Link attr t ('#':url, tit)) = + Link attr t (addHash s url, tit) fixInlineIRs _ v = v normalisePath :: Inline -> Inline -normalisePath (Link t (url, tit)) = +normalisePath (Link attr t (url, tit)) = let (path, uid) = span (/= '#') url in - Link t (takeFileName path ++ uid, tit) + Link attr t (takeFileName path ++ uid, tit) normalisePath s = s 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] = - Link is ('#':url, tit) + Link attr is ('#':url, tit) | otherwise = l prependHash _ i = i diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index d0ee893f2..5a93e0d5b 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -576,16 +576,8 @@ pLineBreak = do return B.linebreak pLink :: TagParser Inlines -pLink = pRelLink <|> pAnchor - -pAnchor :: TagParser Inlines -pAnchor = try $ do - tag <- pSatisfy (tagOpenLit "a" (isJust . lookup "id")) - return $ B.spanWith (fromAttrib "id" tag , [], []) mempty - -pRelLink :: TagParser Inlines -pRelLink = try $ do - tag <- pSatisfy (tagOpenLit "a" (isJust . lookup "href")) +pLink = try $ do + tag <- pSatisfy $ tagOpenLit "a" (const True) mbBaseHref <- baseHref <$> getState let url' = fromAttrib "href" tag let url = case (isURI url', mbBaseHref) of @@ -593,11 +585,9 @@ pRelLink = try $ do _ -> url' let title = fromAttrib "title" tag let uid = fromAttrib "id" tag - let spanC = case uid of - [] -> id - s -> B.spanWith (s, [], []) + let cls = words $ fromAttrib "class" tag lab <- trimInlines . mconcat <$> manyTill inline (pCloses "a") - return $ spanC $ B.link (escapeURI url) title lab + return $ B.linkWith (escapeURI url) title (uid, cls, []) lab pImage :: TagParser Inlines pImage = do diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 8969c3176..4138d65ea 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -814,7 +814,7 @@ substKey = try $ do -- use alt unless :alt: attribute on image: [Para [Image _ [Str "image"] (src,tit)]] -> 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) [Para ils] -> return $ B.fromList ils _ -> mzero diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index a816af8b9..a86e5da95 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -507,8 +507,8 @@ normalizeInlines (Note bs : ys) = Note (normalizeBlocks bs) : normalizeInlines ys normalizeInlines (Quoted qt ils : ys) = Quoted qt (normalizeInlines ils) : normalizeInlines ys -normalizeInlines (Link ils t : ys) = - Link (normalizeInlines ils) t : normalizeInlines ys +normalizeInlines (Link attr ils t : ys) = + Link attr (normalizeInlines ils) t : normalizeInlines ys normalizeInlines (Image attr ils t : ys) = Image attr (normalizeInlines ils) t : normalizeInlines ys normalizeInlines (Cite cs ils : ys) = diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index 8b36ef5c6..4e8c96907 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -394,7 +394,7 @@ inlineToAsciiDoc _ (RawInline f s) inlineToAsciiDoc _ (LineBreak) = return $ " +" <> cr inlineToAsciiDoc _ Space = return space 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] -- abs: http://google.cod[Google] -- or my@email.com[email john] diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs index c65b8de37..c2d476641 100644 --- a/src/Text/Pandoc/Writers/CommonMark.hs +++ b/src/Text/Pandoc/Writers/CommonMark.hs @@ -153,7 +153,7 @@ inlineToNodes (SmallCaps xs) = ((node (INLINE_HTML (T.pack "")) [] : inlinesToNodes xs ++ [node (INLINE_HTML (T.pack "")) []]) ++ ) -inlineToNodes (Link ils (url,tit)) = +inlineToNodes (Link _ ils (url,tit)) = (node (LINK (T.pack url) (T.pack tit)) (inlinesToNodes ils) :) inlineToNodes (Image _ ils (url,tit)) = (node (IMAGE (T.pack url) (T.pack tit)) (inlinesToNodes ils) :) diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 97f61dac8..56fcd4b0b 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -303,7 +303,7 @@ inlineToConTeXt (RawInline _ _) = return empty inlineToConTeXt (LineBreak) = return $ text "\\crlf" <> cr inlineToConTeXt Space = return space -- Handle HTML-like internal document references to sections -inlineToConTeXt (Link txt (('#' : ref), _)) = do +inlineToConTeXt (Link _ txt (('#' : ref), _)) = do opts <- gets stOptions contents <- inlineListToConTeXt txt let ref' = toLabel $ stringToConTeXt opts ref @@ -311,7 +311,7 @@ inlineToConTeXt (Link txt (('#' : ref), _)) = do <> braces contents <> brackets (text ref') -inlineToConTeXt (Link txt (src, _)) = do +inlineToConTeXt (Link _ txt (src, _)) = do let isAutolink = txt == [Str (unEscapeString src)] st <- get let next = stNextRef st @@ -326,10 +326,9 @@ inlineToConTeXt (Link txt (src, _)) = do else brackets empty <> brackets contents) <> "\\from" <> brackets (text ref) -inlineToConTeXt (Image attr _ (src, _)) = do +inlineToConTeXt (Image attr@(_,cls,_) _ (src, _)) = do opts <- gets stOptions - let (_,cls,_) = attr - showDim dir = let d = text (show dir) <> "=" + let showDim dir = let d = text (show dir) <> "=" in case (dimension dir attr) of Just (Pixel a) -> [d <> text (showInInch opts (Pixel a)) <> "in"] diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index 18b1bec5f..8f2810932 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -309,7 +309,7 @@ inlineToCustom lua (RawInline format str) = inlineToCustom lua (LineBreak) = callfunc lua "LineBreak" -inlineToCustom lua (Link txt (src,tit)) = +inlineToCustom lua (Link _ txt (src,tit)) = callfunc lua "Link" txt src tit inlineToCustom lua (Image _ alt (src,tit)) = diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index af289d45e..e3444d257 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -153,16 +153,9 @@ listItemToDocbook opts item = inTagsIndented "listitem" $ blocksToDocbook opts $ map plainToPara item imageToDocbook :: WriterOptions -> Attr -> String -> Doc -imageToDocbook _ attr src = selfClosingTag "imagedata" $ ("fileref", src):ident - ++ roles ++ dims +imageToDocbook _ attr src = selfClosingTag "imagedata" $ + ("fileref", src) : idAndRole attr ++ dims where - (idStr,cls,_) = attr - ident = if null idStr - then [] - else [("id", idStr)] - roles = if null cls - then [] - else [("role", unwords cls)] dims = go Width "width" ++ go Height "depth" go dir dstr = case (dimension dir attr) of Just a -> [(dstr, show a)] @@ -339,7 +332,7 @@ inlineToDocbook _ (RawInline f x) | f == "html" || f == "docbook" = text x | otherwise = empty inlineToDocbook _ LineBreak = text "\n" inlineToDocbook _ Space = space -inlineToDocbook opts (Link txt (src, _)) +inlineToDocbook opts (Link attr txt (src, _)) | Just email <- stripPrefix "mailto:" src = let emailLink = inTagsSimple "email" $ text $ escapeStringForXML $ email @@ -349,8 +342,8 @@ inlineToDocbook opts (Link txt (src, _)) char '(' <> emailLink <> char ')' | otherwise = (if isPrefixOf "#" src - then inTags False "link" [("linkend", drop 1 src)] - else inTags False "ulink" [("url", src)]) $ + then inTags False "link" $ ("linkend", drop 1 src) : idAndRole attr + else inTags False "ulink" $ ("url", src) : idAndRole attr ) $ inlinesToDocbook opts txt inlineToDocbook opts (Image attr _ (src, tit)) = let titleDoc = if null tit @@ -365,3 +358,14 @@ inlineToDocbook opts (Note contents) = isMathML :: HTMLMathMethod -> Bool isMathML (MathML _) = True 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)] + diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index a17be3ca0..e9f256210 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -1087,11 +1087,11 @@ inlineToOpenXML opts (Note bs) = do [ mknode "w:rPr" [] footnoteStyle , mknode "w:footnoteReference" [("w:id", notenum)] () ] ] -- internal link: -inlineToOpenXML opts (Link txt ('#':xs,_)) = do +inlineToOpenXML opts (Link _ txt ('#':xs,_)) = do contents <- withTextPropM (rStyleM "Hyperlink") $ inlinesToOpenXML opts txt return [ mknode "w:hyperlink" [("w:anchor",xs)] contents ] -- external link: -inlineToOpenXML opts (Link txt (src,_)) = do +inlineToOpenXML opts (Link _ txt (src,_)) = do contents <- withTextPropM (rStyleM "Hyperlink") $ inlinesToOpenXML opts txt extlinks <- gets stExternalLinks id' <- case M.lookup src extlinks of diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index 915821050..ebd5f8d70 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -464,13 +464,13 @@ inlineToDokuWiki _ (LineBreak) = return "\\\\\n" inlineToDokuWiki _ Space = return " " -inlineToDokuWiki opts (Link txt (src, _)) = do +inlineToDokuWiki opts (Link _ txt (src, _)) = do label <- inlineListToDokuWiki opts txt case txt of [Str s] | "mailto:" `isPrefixOf` src -> return $ "<" ++ s ++ ">" | escapeURI s == src -> return src _ -> if isURI src - then return $ "[[" ++ src ++ "|" ++ label ++ "]]" + then return $ "[[" ++ src ++ "|" ++ label ++ "]]" else return $ "[[" ++ src' ++ "|" ++ label ++ "]]" where src' = case src of '/':xs -> xs -- with leading / it's a diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 950d5cde3..c3e295c8f 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -457,10 +457,10 @@ writeEPUB opts doc@(Pandoc meta _) = do chapters' [1..] let fixInternalReferences :: Inline -> Inline - fixInternalReferences (Link lab ('#':xs, tit)) = + fixInternalReferences (Link attr lab ('#':xs, tit)) = case lookup xs reftable of - Just ys -> Link lab (ys, tit) - Nothing -> Link lab ('#':xs, tit) + Just ys -> Link attr lab (ys, tit) + Nothing -> Link attr lab ('#':xs, tit) fixInternalReferences x = x -- internal reference IDs change when we chunk the file, diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index f8f007185..bc936fce5 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -442,7 +442,7 @@ toXml Space = return [txt " "] toXml LineBreak = return [el "empty-line" ()] toXml (Math _ formula) = insertMath InlineImage formula 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 let n = 1 + length fns let ln_id = linkID n @@ -572,7 +572,7 @@ plain Space = " " plain LineBreak = "\n" plain (Math _ 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 (Note _) = "" -- FIXME diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index 436c5b343..ab158b38d 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -363,10 +363,10 @@ parseMailto s = do _ -> fail "not a mailto: URL" -- | Obfuscate a "mailto:" link. -obfuscateLink :: WriterOptions -> Html -> String -> Html -obfuscateLink opts txt s | writerEmailObfuscation opts == NoObfuscation = - H.a ! A.href (toValue s) $ txt -obfuscateLink opts (renderHtml -> txt) s = +obfuscateLink :: WriterOptions -> Attr -> Html -> String -> Html +obfuscateLink opts attr txt s | writerEmailObfuscation opts == NoObfuscation = + addAttrs opts attr $ H.a ! A.href (toValue s) $ txt +obfuscateLink opts attr (renderHtml -> txt) s = let meth = writerEmailObfuscation opts s' = map toLower (take 7 s) ++ drop 7 s in case parseMailto s' of @@ -392,7 +392,7 @@ obfuscateLink opts (renderHtml -> txt) s = linkText ++ "+'<\\/'+'a'+'>');\n// -->\n")) >> H.noscript (preEscapedString $ obfuscateString altText) _ -> 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. obfuscateChar :: Char -> String @@ -808,10 +808,10 @@ inlineToHtml opts inline = _ -> return mempty | f == Format "html" -> return $ preEscapedString str | otherwise -> return mempty - (Link txt (s,_)) | "mailto:" `isPrefixOf` s -> do + (Link attr txt (s,_)) | "mailto:" `isPrefixOf` s -> do linkText <- inlineListToHtml opts txt - return $ obfuscateLink opts linkText s - (Link txt (s,tit)) -> do + return $ obfuscateLink opts attr linkText s + (Link attr txt (s,tit)) -> do linkText <- inlineListToHtml opts txt let s' = case s of '#':xs | writerSlideVariant opts == @@ -821,9 +821,10 @@ inlineToHtml opts inline = let link' = if txt == [Str (unEscapeString s)] then link ! A.class_ "uri" else link + let link'' = addAttrs opts attr link' return $ if null tit - then link' - else link' ! A.title (toValue tit) + then link'' + else link'' ! A.title (toValue tit) (Image attr txt (s,tit)) | treatAsImage s -> do let alternate' = stringify txt let attributes = [A.src $ toValue s] ++ @@ -874,7 +875,7 @@ blockListToNote :: WriterOptions -> String -> [Block] -> State WriterState Html blockListToNote opts ref blocks = -- 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. - let backlink = [Link [Str "↩"] ("#" ++ writerIdentifierPrefix opts ++ "fnref" ++ ref,[])] + let backlink = [Link nullAttr [Str "↩"] ("#" ++ writerIdentifierPrefix opts ++ "fnref" ++ ref,[])] blocks' = if null blocks then [] else let lastBlock = last blocks diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 49a9953b6..a3188c647 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -327,7 +327,7 @@ inlineToHaddock _ (RawInline f str) inlineToHaddock _ (LineBreak) = return cr inlineToHaddock _ Space = return space inlineToHaddock opts (Cite _ lst) = inlineListToHaddock opts lst -inlineToHaddock opts (Link txt (src, _)) = do +inlineToHaddock opts (Link _ txt (src, _)) = do linktext <- inlineListToHaddock opts txt let useAuto = isURI src && case txt of @@ -335,8 +335,8 @@ inlineToHaddock opts (Link txt (src, _)) = do _ -> False return $ nowrap $ "<" <> text src <> (if useAuto then empty else space <> linktext) <> ">" -inlineToHaddock opts (Image _ alternate (source, tit)) = do - linkhaddock <- inlineToHaddock opts (Link alternate (source, tit)) +inlineToHaddock opts (Image attr alternate (source, tit)) = do + linkhaddock <- inlineToHaddock opts (Link attr alternate (source, tit)) return $ "<" <> linkhaddock <> ">" -- haddock doesn't have notes, but we can fake it: inlineToHaddock opts (Note contents) = do diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 71e541b6f..2bbd3b44f 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -419,7 +419,7 @@ inlineToICML _ style (Math _ str) = charStyle style $ text $ escapeStringForXML inlineToICML _ _ (RawInline f str) | f == Format "icml" = return $ text str | 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 state $ \st -> let ident = if null $ links st diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 76ad1c510..5857723a6 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -99,8 +99,8 @@ pandocToLaTeX options (Pandoc meta blocks) = do _ -> blocks else blocks -- see if there are internal links - let isInternalLink (Link _ ('#':xs,_)) = [xs] - isInternalLink _ = [] + let isInternalLink (Link _ _ ('#':xs,_)) = [xs] + isInternalLink _ = [] modify $ \s -> s{ stInternalLinks = query isInternalLink blocks' } let template = writerTemplate options -- set stBook depending on documentclass @@ -620,8 +620,8 @@ defListItemToLaTeX (term, defs) = do 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 isInternalLink (Link _ _ ('#':_,_)) = True + isInternalLink _ = False let term'' = if any isInternalLink term then braces term' else term' @@ -828,11 +828,11 @@ inlineToLaTeX (RawInline f str) | otherwise = return empty inlineToLaTeX (LineBreak) = return $ "\\\\" <> cr inlineToLaTeX Space = return space -inlineToLaTeX (Link txt ('#':ident, _)) = do +inlineToLaTeX (Link _ txt ('#':ident, _)) = do contents <- inlineListToLaTeX txt lab <- toLabel ident return $ text "\\hyperref" <> brackets (text lab) <> braces contents -inlineToLaTeX (Link txt (src, _)) = +inlineToLaTeX (Link _ txt (src, _)) = case txt of [Str x] | escapeURI x == src -> -- autolink do modify $ \s -> s{ stUrl = True } diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index 5a49428f6..71fd145e2 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -342,7 +342,7 @@ inlineToMan _ (RawInline f str) inlineToMan _ (LineBreak) = return $ cr <> text ".PD 0" $$ text ".P" $$ text ".PD" <> cr inlineToMan _ Space = return space -inlineToMan opts (Link txt (src, _)) = do +inlineToMan opts (Link _ txt (src, _)) = do linktext <- inlineListToMan opts txt let srcSuffix = fromMaybe src (stripPrefix "mailto:" src) return $ case txt of @@ -350,12 +350,12 @@ inlineToMan opts (Link txt (src, _)) = do | escapeURI s == srcSuffix -> char '<' <> text srcSuffix <> 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 ""]) || (alternate == [Str source]) -- to prevent autolinks then [Str "image"] else alternate - linkPart <- inlineToMan opts (Link txt (source, tit)) + linkPart <- inlineToMan opts (Link attr txt (source, tit)) return $ char '[' <> text "IMAGE: " <> linkPart <> char ']' inlineToMan _ (Note contents) = do -- add to notes in state diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index f809e5d19..019a0e272 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -55,7 +55,8 @@ import qualified Data.Vector as V import qualified Data.Text as T type Notes = [[Block]] -type Refs = [([Inline], Target)] +type Ref = ([Inline], Target, Attr) +type Refs = [Ref] data WriterState = WriterState { stNotes :: Notes , stRefs :: Refs , stRefShortcutable :: Bool @@ -200,15 +201,16 @@ refsToMarkdown opts refs = mapM (keyToMarkdown opts) refs >>= return . vcat -- | Return markdown representation of a reference key. keyToMarkdown :: WriterOptions - -> ([Inline], (String, String)) + -> Ref -> State WriterState Doc -keyToMarkdown opts (label, (src, tit)) = do +keyToMarkdown opts (label, (src, tit), attr) = do label' <- inlineListToMarkdown opts label let tit' = if null tit then empty else space <> "\"" <> text tit <> "\"" return $ nest 2 $ hang 2 ("[" <> label' <> "]:" <> space) (text src <> tit') + <> linkAttributes opts attr -- | Return markdown representation of notes. notesToMarkdown :: WriterOptions -> [[Block]] -> State WriterState Doc @@ -280,6 +282,12 @@ attrsToMarkdown attribs = braces $ hsep [attribId, attribClasses, attribKeys] map (\(k,v) -> text k <> "=\"" <> 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. olMarker :: Parser [Char] ParserState Char olMarker = do (start, style', delim) <- anyOrderedListMarker @@ -665,21 +673,21 @@ blockListToMarkdown opts blocks = -- | Get reference for target; if none exists, create unique one and return. -- Prefer label if possible; otherwise, generate a unique key. -getReference :: [Inline] -> Target -> State WriterState [Inline] -getReference label (src, tit) = do +getReference :: Attr -> [Inline] -> Target -> State WriterState [Inline] +getReference attr label target = do st <- get - case find ((== (src, tit)) . snd) (stRefs st) of - Just (ref, _) -> return ref + case find (\(_,t,a) -> t == target && a == attr) (stRefs st) of + Just (ref, _, _) -> return ref 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 case find (\n -> notElem [Str (show n)] - (map fst (stRefs st))) + (map (\(l,_,_) -> l) (stRefs st))) [1..(10000 :: Integer)] of Just x -> [Str (show x)] Nothing -> error "no unique label" Nothing -> label - modify (\s -> s{ stRefs = (label', (src,tit)) : stRefs st }) + modify (\s -> s{ stRefs = (label', target, attr) : stRefs st }) return label' -- | Convert list of Pandoc inline elements to markdown. @@ -689,10 +697,10 @@ inlineListToMarkdown opts lst = do go (if inlist then avoidBadWrapsInList lst else lst) where go [] = return empty 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 - (Link _ _):_ -> unshortcutable - Space:(Link _ _):_ -> unshortcutable + (Link _ _ _):_ -> unshortcutable + Space:(Link _ _ _):_ -> unshortcutable Space:(Str('[':_)):_ -> unshortcutable Space:(RawInline _ ('[':_)):_ -> unshortcutable Space:(Cite _ _):_ -> unshortcutable @@ -883,7 +891,7 @@ inlineToMarkdown opts (Cite (c:cs) lst) return $ pdoc <+> r modekey SuppressAuthor = "-" modekey _ = "" -inlineToMarkdown opts (Link txt (src, tit)) = do +inlineToMarkdown opts (Link attr txt (src, tit)) = do plain <- gets stPlain linktext <- inlineListToMarkdown opts txt let linktitle = if null tit @@ -898,7 +906,7 @@ inlineToMarkdown opts (Link txt (src, tit)) = do shortcutable <- gets stRefShortcutable let useShortcutRefLinks = shortcutable && 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 return $ if useAuto then if plain @@ -915,21 +923,18 @@ inlineToMarkdown opts (Link txt (src, tit)) = do else if plain then linktext else "[" <> linktext <> "](" <> - text src <> linktitle <> ")" + text src <> linktitle <> ")" <> + linkAttributes opts attr inlineToMarkdown opts (Image attr alternate (source, tit)) = do plain <- gets stPlain let txt = if null alternate || alternate == [Str source] -- to prevent autolinks then [Str ""] else alternate - linkPart <- inlineToMarkdown opts (Link txt (source, tit)) + linkPart <- inlineToMarkdown opts (Link attr txt (source, tit)) return $ if plain then "[" <> linkPart <> "]" - else "!" <> linkPart <> - if isEnabled Ext_common_link_attributes opts - && attr /= nullAttr - then attrsToMarkdown attr - else empty + else "!" <> linkPart inlineToMarkdown opts (Note contents) = do modify (\st -> st{ stNotes = contents : stNotes st }) st <- get diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 5c51157ea..1aae15354 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -399,7 +399,7 @@ inlineToMediaWiki (LineBreak) = return "
\n" inlineToMediaWiki Space = return " " -inlineToMediaWiki (Link txt (src, _)) = do +inlineToMediaWiki (Link _ txt (src, _)) = do label <- inlineListToMediaWiki txt case txt of [Str s] | isURI src && escapeURI s == src -> return src diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 1935a630f..7b964e2d2 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -393,7 +393,7 @@ inlineToOpenDocument o ils | RawInline f s <- ils = if f == Format "opendocument" then return $ text s 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 attr _ (s,t) <- ils = mkImg attr s t | Note l <- ils = mkNote l | otherwise = return empty diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index ffd271810..24da7b9e1 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -276,7 +276,7 @@ inlineToOrg (RawInline f str) | f == "tex" || f == "latex" = return $ text str inlineToOrg (RawInline _ _) = return empty inlineToOrg (LineBreak) = return (text "\\\\" <> cr) inlineToOrg Space = return space -inlineToOrg (Link txt (src, _)) = do +inlineToOrg (Link _ txt (src, _)) = do case txt of [Str x] | escapeURI x == src -> -- autolink do modify $ \s -> s{ stLinks = True } diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index 4b68984d0..a65d6f8bb 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -390,7 +390,7 @@ inlineListToRST lst = isComplex (Strikeout _) = True isComplex (Superscript _) = True isComplex (Subscript _) = True - isComplex (Link _ _) = True + isComplex (Link _ _ _) = True isComplex (Image _ _ _) = True isComplex (Code _ _) = True isComplex (Math _ _) = True @@ -442,17 +442,17 @@ inlineToRST (RawInline f x) inlineToRST (LineBreak) = return cr -- there's no line break in RST (see Para) inlineToRST Space = return space -- autolink -inlineToRST (Link [Str str] (src, _)) +inlineToRST (Link _ [Str str] (src, _)) | isURI src && if "mailto:" `isPrefixOf` src then src == escapeURI ("mailto:" ++ str) else src == escapeURI str = do let srcSuffix = fromMaybe src (stripPrefix "mailto:" src) return $ text srcSuffix -inlineToRST (Link [Image attr alt (imgsrc,imgtit)] (src, _tit)) = do +inlineToRST (Link _ [Image attr alt (imgsrc,imgtit)] (src, _tit)) = do label <- registerImage attr alt (imgsrc,imgtit) (Just src) return $ "|" <> label <> "|" -inlineToRST (Link txt (src, tit)) = do +inlineToRST (Link _ txt (src, tit)) = do useReferenceLinks <- get >>= return . writerReferenceLinks . stOptions linktext <- inlineListToRST $ normalizeSpaces txt if useReferenceLinks diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index c89e88fad..dabe5cf78 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -350,7 +350,7 @@ inlineToRTF (RawInline f str) | otherwise = "" inlineToRTF (LineBreak) = "\\line " inlineToRTF Space = " " -inlineToRTF (Link text (src, _)) = +inlineToRTF (Link _ text (src, _)) = "{\\field{\\*\\fldinst{HYPERLINK \"" ++ (codeStringToRTF src) ++ "\"}}{\\fldrslt{\\ul\n" ++ (inlineListToRTF text) ++ "\n}}}\n" inlineToRTF (Image _ _ (source, _)) = diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index a8e1e15a6..cd9e2ef3d 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -427,11 +427,11 @@ inlineToTexinfo (RawInline f str) inlineToTexinfo (LineBreak) = return $ text "@*" <> cr inlineToTexinfo Space = return space -inlineToTexinfo (Link txt (src@('#':_), _)) = do +inlineToTexinfo (Link _ txt (src@('#':_), _)) = do contents <- escapeCommas $ inlineListToTexinfo txt return $ text "@ref" <> braces (text (stringToTexinfo src) <> text "," <> contents) -inlineToTexinfo (Link txt (src, _)) = do +inlineToTexinfo (Link _ txt (src, _)) = do case txt of [Str x] | escapeURI x == src -> -- autolink do return $ text $ "@url{" ++ x ++ "}" diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index dde9a7177..456bf19c9 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -426,23 +426,25 @@ inlineToTextile _ (LineBreak) = return "\n" 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 [Code _ s] | s == src -> return "$" [Str s] | s == src -> return "$" _ -> inlineListToTextile opts txt - return $ "\"" ++ label ++ "\":" ++ src + return $ "\"" ++ classes ++ label ++ "\":" ++ src -inlineToTextile opts (Image attr alt (source, tit)) = do +inlineToTextile opts (Image attr@(_, cls, _) alt (source, tit)) = do alt' <- inlineListToTextile opts alt let txt = if null tit then if null alt' then "" else "(" ++ alt' ++ ")" else "(" ++ tit ++ ")" - (_, cls, _) = attr classes = if null cls then "" else "(" ++ unwords cls ++ ")" From fe2907ca72043b40ea9776cb4706557cfbf22b56 Mon Sep 17 00:00:00 2001 From: mb21 Date: Sun, 26 Jul 2015 18:31:38 +0200 Subject: [PATCH 13/14] Updated Arbitrary instance for link attribute --- tests/Tests/Arbitrary.hs | 5 +++-- 1 file changed, 3 insertions(+), 2 deletions(-) diff --git a/tests/Tests/Arbitrary.hs b/tests/Tests/Arbitrary.hs index de07322fb..d792e1375 100644 --- a/tests/Tests/Arbitrary.hs +++ b/tests/Tests/Arbitrary.hs @@ -56,10 +56,11 @@ arbInline n = frequency $ [ (60, liftM Str realString) , (10, do x1 <- arbitrary x2 <- realString return $ Math x1 x2) - , (10, do x1 <- arbInlines (n-1) + , (10, do x0 <- arbAttr + x1 <- arbInlines (n-1) x3 <- realString x2 <- liftM escapeURI realString - return $ Link x1 (x2,x3)) + return $ Link x0 x1 (x2,x3)) , (10, do x0 <- arbAttr x1 <- arbInlines (n-1) x3 <- realString From 08243d53a68239fe60fdcb59ee71f6562b16f5c7 Mon Sep 17 00:00:00 2001 From: mb21 Date: Sun, 26 Jul 2015 20:09:10 +0200 Subject: [PATCH 14/14] Updated tests for link attribute changes. --- tests/docbook-reader.native | 60 ++++++++++---------- tests/docx/already_auto_ident.native | 2 +- tests/docx/inline_images.native | 2 +- tests/docx/inline_images_writer.native | 2 +- tests/docx/links.native | 8 +-- tests/docx/links_writer.native | 8 +-- tests/epub/features.native | 6 +- tests/epub/formatting.native | 8 +-- tests/epub/wasteland.native | 2 +- tests/haddock-reader.native | 8 +-- tests/html-reader.native | 60 ++++++++++---------- tests/latex-reader.native | 62 ++++++++++----------- tests/markdown-reader-more.native | 50 ++++++++--------- tests/mediawiki-reader.native | 24 ++++---- tests/odt/native/referenceToChapter.native | 2 +- tests/odt/native/referenceToListItem.native | 2 +- tests/odt/native/referenceToText.native | 2 +- tests/opml-reader.native | 2 +- tests/rst-reader.native | 14 ++--- tests/testsuite.native | 62 ++++++++++----------- tests/textile-reader.native | 14 ++--- tests/twiki-reader.native | 8 +-- tests/txt2tags.native | 10 ++-- tests/writer.native | 62 ++++++++++----------- 24 files changed, 240 insertions(+), 240 deletions(-) diff --git a/tests/docbook-reader.native b/tests/docbook-reader.native index 5e76bdc0b..fd4bc06fd 100644 --- a/tests/docbook-reader.native +++ b/tests/docbook-reader.native @@ -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"])]}) [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 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 4 ("level-4",[],[]) [Str "Level",Space,Str "4"] ,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"] ,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 "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 [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."]]] @@ -230,42 +230,42 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Str "Minus:",Space,Str "-"] ,Header 1 ("links",[],[]) [Str "Links"] ,Header 2 ("explicit",[],[]) [Str "Explicit"] -,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/","")] -,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","")] -,Para [Link [Str "with_underscore"] ("/url/with_underscore","")] -,Para [Link [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")] -,Para [Link [Str "Empty"] ("",""),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/","")] +,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","")] +,Para [Link ("",[],[]) [Str "with_underscore"] ("/url/with_underscore","")] +,Para [Link ("",[],[]) [Str "nobody@nowhere.net"] ("mailto:nobody@nowhere.net","")] +,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."] ,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 "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 [Str "Indented",Space,Link [Str "once"] ("/url",""),Str "."] -,Para [Str "Indented",Space,Link [Str "twice"] ("/url",""),Str "."] -,Para [Str "Indented",Space,Link [Str "thrice"] ("/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 [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 "twice"] ("/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."] ,CodeBlock ("",[],[]) "[not]: /url" -,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] -,Para [Str "Foo",Space,Link [Str "biz"] ("/url/",""),Str "."] +,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."] +,Para [Str "Foo",Space,Link ("",[],[]) [Str "biz"] ("/url/",""),Str "."] ,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,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",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?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 "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 "."] ,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 [[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 "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 - [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 ("",[],[]) ""] ,CodeBlock ("",[],[]) "or here: " ,Header 1 ("images",[],[]) [Str "Images"] @@ -274,7 +274,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,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","")] ,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 ("",[],[]) " { }",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 ("",[],[]) " { }",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 [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) diff --git a/tests/docx/already_auto_ident.native b/tests/docx/already_auto_ident.native index 054bfe34a..67c37298d 100644 --- a/tests/docx/already_auto_ident.native +++ b/tests/docx/already_auto_ident.native @@ -1,2 +1,2 @@ [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","")]] diff --git a/tests/docx/inline_images.native b/tests/docx/inline_images.native index ac6e33fc1..aa7231d97 100644 --- a/tests/docx/inline_images.native +++ b/tests/docx/inline_images.native @@ -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 "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."]] diff --git a/tests/docx/inline_images_writer.native b/tests/docx/inline_images_writer.native index a0b63fece..afefe0ebc 100644 --- a/tests/docx/inline_images_writer.native +++ b/tests/docx/inline_images_writer.native @@ -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 "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."]] diff --git a/tests/docx/links.native b/tests/docx/links.native index a05578100..2c4688629 100644 --- a/tests/docx/links.native +++ b/tests/docx/links.native @@ -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"] -,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 "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 "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 "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."] ,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"]] diff --git a/tests/docx/links_writer.native b/tests/docx/links_writer.native index 25f4f90f9..48c1bcd81 100644 --- a/tests/docx/links_writer.native +++ b/tests/docx/links_writer.native @@ -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"] -,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 "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 "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 "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."] ,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"]] diff --git a/tests/epub/features.native b/tests/epub/features.native index 6ccc04f43..96783ac03 100644 --- a/tests/epub/features.native +++ b/tests/epub/features.native @@ -5,14 +5,14 @@ ,Header 2 ("",[],[]) [Str "Status",Space,Str "of",Space,Str "this",Space,Str "Document"] ,Para [Str "This",Space,Str "publication",Space,Str "is",Space,Str "currently",Space,Str "considered",Space,Span ("",["status"],[]) [Str "[UNDER",Space,Str "DEVELOPMENT]"],Space,Str "by",Space,Str "the",Space,Str "IDPF."] ,Para [Str "This",Space,Str "publication",Space,Str "is",Space,Str "part",Space,Str "of",Space,Str "version",Space,Span ("",["version"],[]) [Str "X.X"],Space,Str "of",Space,Str "the",Space,Str "EPUB",Space,Str "3.0",Space,Str "Compliance",Space,Str "Test",Space,Str "Suite",Space,Str "released",Space,Str "on",Space,RawInline (Format "html") "",Str "."] -,Para [Str "Before",Space,Str "using",Space,Str "this",Space,Str "publication",Space,Str "to",Space,Str "evaluate",Space,Str "reading",Space,Str "systems,",Space,Str "testers",Space,Str "are",Space,Str "strongly",Space,Str "encouraged",Space,Str "to",Space,Str "verify",Space,Str "that",Space,Str "they",Space,Str "have",Space,Str "the",Space,Str "latest",Space,Str "release",Space,Str "by",Space,Str "checking",Space,Str "the",Space,Str "current",Space,Str "release",Space,Str "version",Space,Str "and",Space,Str "date",Space,Str "of",Space,Str "the",Space,Str "test",Space,Str "suite",Space,Str "at",Space,Link [Str "TBD"] ("","")] +,Para [Str "Before",Space,Str "using",Space,Str "this",Space,Str "publication",Space,Str "to",Space,Str "evaluate",Space,Str "reading",Space,Str "systems,",Space,Str "testers",Space,Str "are",Space,Str "strongly",Space,Str "encouraged",Space,Str "to",Space,Str "verify",Space,Str "that",Space,Str "they",Space,Str "have",Space,Str "the",Space,Str "latest",Space,Str "release",Space,Str "by",Space,Str "checking",Space,Str "the",Space,Str "current",Space,Str "release",Space,Str "version",Space,Str "and",Space,Str "date",Space,Str "of",Space,Str "the",Space,Str "test",Space,Str "suite",Space,Str "at",Space,Link ("",[],[]) [Str "TBD"] ("","")] ,Para [Str "This",Space,Str "publication",Space,Str "is",Space,Str "one",Space,Str "of",Space,Str "several",Space,Str "that",Space,Str "currently",Space,Str "comprise",Space,Str "the",Space,Str "EPUB",Space,Str "3",Space,Str "conformance",Space,Str "test",Space,Str "suite",Space,Str "for",Space,Str "reflowable",Space,Str "content.",Space,Str "The",Space,Str "complete",Space,Str "test",Space,Str "suite",Space,Str "includes",Space,Str "all",Space,Str "of",Space,Str "the",Space,Str "following",Space,Str "publications:"] ,OrderedList (1,DefaultStyle,DefaultDelim) [[Plain [Str "."]]] ,RawBlock (Format "html") "" ,RawBlock (Format "html") "
" ,Header 2 ("",[],[]) [Str "About",Space,Str "this",Space,Str "Document"] -,Para [Str "This",Space,Str "document",Space,Str "focuses",Space,Str "on",Space,Str "human-evaluated",Space,Str "binary",Space,Str "(pass/fail)",Space,Str "tests",Space,Str "in",Space,Str "a",Space,Str "reflowable",Space,Str "context.",Space,Str "Tests",Space,Str "for",Space,Str "fixed-layout",Space,Str "content",Space,Str "and",Space,Str "other",Space,Str "individual",Space,Str "tests",Space,Str "that",Space,Str "require",Space,Str "a",Space,Str "dedicated",Space,Str "epub",Space,Str "file",Space,Str "are",Space,Str "available",Space,Str "in",Space,Str "additional",Space,Str "sibling",Space,Str "documents;",Space,Str "refer",Space,Str "to",Space,Str "the",Space,Link [Str "test",Space,Str "suite",Space,Str "wiki"] ("Overview",""),Space,Str "(",Code ("",[],[]) "https://github.com/mgylling/epub-testsuite/wiki/Overview",Str ")",Space,Str "for",Space,Str "additional",Space,Str "information."] +,Para [Str "This",Space,Str "document",Space,Str "focuses",Space,Str "on",Space,Str "human-evaluated",Space,Str "binary",Space,Str "(pass/fail)",Space,Str "tests",Space,Str "in",Space,Str "a",Space,Str "reflowable",Space,Str "context.",Space,Str "Tests",Space,Str "for",Space,Str "fixed-layout",Space,Str "content",Space,Str "and",Space,Str "other",Space,Str "individual",Space,Str "tests",Space,Str "that",Space,Str "require",Space,Str "a",Space,Str "dedicated",Space,Str "epub",Space,Str "file",Space,Str "are",Space,Str "available",Space,Str "in",Space,Str "additional",Space,Str "sibling",Space,Str "documents;",Space,Str "refer",Space,Str "to",Space,Str "the",Space,Link ("",[],[]) [Str "test",Space,Str "suite",Space,Str "wiki"] ("Overview",""),Space,Str "(",Code ("",[],[]) "https://github.com/mgylling/epub-testsuite/wiki/Overview",Str ")",Space,Str "for",Space,Str "additional",Space,Str "information."] ,RawBlock (Format "html") "
" ,RawBlock (Format "html") "
" ,Header 2 ("",[],[]) [Str "Conventions"] @@ -74,7 +74,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"] ,Para [Str "Tests",Space,Str "whether",Space,Code ("",[],[]) "mtable",Space,Str "with",Space,Code ("",[],[]) "colspan",Space,Str "and",Space,Code ("",[],[]) "mspace",Space,Str "attributes",Space,Str "(colum",Space,Str "and",Space,Str "row",Space,Str "spanning)",Space,Str "are",Space,Str "supported;",Space,Str "uses",Space,Str "Hebrew",Space,Str "and",Space,Str "Script",Space,Str "alphabets."] ,Para [Math DisplayMath "\\begin{array}{llllllllll}\n & {\\operatorname{cov}\\left( \\mathcal{L} \\right)} & \\longrightarrow & {\\operatorname{non}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cof}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cof}\\left( \\mathcal{L} \\right)} & \\longrightarrow & 2^{\\aleph_{0}} \\\\\n & \\uparrow & & \\uparrow & & \\uparrow & & \\uparrow & & \\\\\n & {\\mathfrak{b}} & \\longrightarrow & {\\mathfrak{d}} & & & & & & \\\\\n & \\uparrow & & \\uparrow & & & & & & \\\\\n\\aleph_{1} & \\longrightarrow & {\\operatorname{add}\\left( \\mathcal{L} \\right)} & \\longrightarrow & {\\operatorname{add}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{cov}\\left( \\mathcal{K} \\right)} & \\longrightarrow & {\\operatorname{non}\\left( \\mathcal{L} \\right)} & \\\\\n\\end{array}"] -,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Link [Str "Cicho\324's",Space,Str "Diagram"] ("Cicho%C5%84's_diagram",""),Str ":",Space,Str "."] +,Para [Str "The",Space,Str "test",Space,Str "passes",Space,Str "if",Space,Str "the",Space,Str "rendering",Space,Str "looks",Space,Str "like",Space,Link ("",[],[]) [Str "Cicho\324's",Space,Str "Diagram"] ("Cicho%C5%84's_diagram",""),Str ":",Space,Str "."] ,RawBlock (Format "html") "
" ,RawBlock (Format "html") "
" ,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"] diff --git a/tests/epub/formatting.native b/tests/epub/formatting.native index bdf86fa20..82655c6cc 100644 --- a/tests/epub/formatting.native +++ b/tests/epub/formatting.native @@ -5,14 +5,14 @@ ,Header 2 ("",[],[]) [Str "Status",Space,Str "of",Space,Str "this",Space,Str "Document"] ,Para [Str "This",Space,Str "publication",Space,Str "is",Space,Str "currently",Space,Str "considered",Space,Span ("",["status"],[]) [Str "[UNDER",Space,Str "DEVELOPMENT]"],Space,Str "by",Space,Str "the",Space,Str "IDPF."] ,Para [Str "This",Space,Str "publication",Space,Str "is",Space,Str "part",Space,Str "of",Space,Str "version",Space,Span ("",["version"],[]) [Str "X.X"],Space,Str "of",Space,Str "the",Space,Str "EPUB",Space,Str "3.0",Space,Str "Compliance",Space,Str "Test",Space,Str "Suite",Space,Str "released",Space,Str "on",Space,RawInline (Format "html") "",Str "."] -,Para [Str "Before",Space,Str "using",Space,Str "this",Space,Str "publication",Space,Str "to",Space,Str "evaluate",Space,Str "reading",Space,Str "systems,",Space,Str "testers",Space,Str "are",Space,Str "strongly",Space,Str "encouraged",Space,Str "to",Space,Str "verify",Space,Str "that",Space,Str "they",Space,Str "have",Space,Str "the",Space,Str "latest",Space,Str "release",Space,Str "by",Space,Str "checking",Space,Str "the",Space,Str "current",Space,Str "release",Space,Str "version",Space,Str "and",Space,Str "date",Space,Str "of",Space,Str "the",Space,Str "test",Space,Str "suite",Space,Str "at",Space,Link [Str "TBD"] ("","")] +,Para [Str "Before",Space,Str "using",Space,Str "this",Space,Str "publication",Space,Str "to",Space,Str "evaluate",Space,Str "reading",Space,Str "systems,",Space,Str "testers",Space,Str "are",Space,Str "strongly",Space,Str "encouraged",Space,Str "to",Space,Str "verify",Space,Str "that",Space,Str "they",Space,Str "have",Space,Str "the",Space,Str "latest",Space,Str "release",Space,Str "by",Space,Str "checking",Space,Str "the",Space,Str "current",Space,Str "release",Space,Str "version",Space,Str "and",Space,Str "date",Space,Str "of",Space,Str "the",Space,Str "test",Space,Str "suite",Space,Str "at",Space,Link ("",[],[]) [Str "TBD"] ("","")] ,Para [Str "This",Space,Str "publication",Space,Str "is",Space,Str "one",Space,Str "of",Space,Str "several",Space,Str "that",Space,Str "currently",Space,Str "comprise",Space,Str "the",Space,Str "EPUB",Space,Str "3",Space,Str "conformance",Space,Str "test",Space,Str "suite",Space,Str "for",Space,Str "reflowable",Space,Str "content.",Space,Str "The",Space,Str "complete",Space,Str "test",Space,Str "suite",Space,Str "includes",Space,Str "all",Space,Str "of",Space,Str "the",Space,Str "following",Space,Str "publications:"] ,OrderedList (1,DefaultStyle,DefaultDelim) [[Plain [Str "."]]] ,RawBlock (Format "html") "
" ,RawBlock (Format "html") "
" ,Header 2 ("",[],[]) [Str "About",Space,Str "this",Space,Str "Document"] -,Para [Str "This",Space,Str "document",Space,Str "focuses",Space,Str "on",Space,Str "human-evaluated",Space,Str "binary",Space,Str "(pass/fail)",Space,Str "tests",Space,Str "in",Space,Str "a",Space,Str "reflowable",Space,Str "context.",Space,Str "Tests",Space,Str "for",Space,Str "fixed-layout",Space,Str "content",Space,Str "and",Space,Str "other",Space,Str "individual",Space,Str "tests",Space,Str "that",Space,Str "require",Space,Str "a",Space,Str "dedicated",Space,Str "epub",Space,Str "file",Space,Str "are",Space,Str "available",Space,Str "in",Space,Str "additional",Space,Str "sibling",Space,Str "documents;",Space,Str "refer",Space,Str "to",Space,Str "the",Space,Link [Str "test",Space,Str "suite",Space,Str "wiki"] ("Overview",""),Space,Str "(",Code ("",[],[]) "https://github.com/mgylling/epub-testsuite/wiki/Overview",Str ")",Space,Str "for",Space,Str "additional",Space,Str "information."] +,Para [Str "This",Space,Str "document",Space,Str "focuses",Space,Str "on",Space,Str "human-evaluated",Space,Str "binary",Space,Str "(pass/fail)",Space,Str "tests",Space,Str "in",Space,Str "a",Space,Str "reflowable",Space,Str "context.",Space,Str "Tests",Space,Str "for",Space,Str "fixed-layout",Space,Str "content",Space,Str "and",Space,Str "other",Space,Str "individual",Space,Str "tests",Space,Str "that",Space,Str "require",Space,Str "a",Space,Str "dedicated",Space,Str "epub",Space,Str "file",Space,Str "are",Space,Str "available",Space,Str "in",Space,Str "additional",Space,Str "sibling",Space,Str "documents;",Space,Str "refer",Space,Str "to",Space,Str "the",Space,Link ("",[],[]) [Str "test",Space,Str "suite",Space,Str "wiki"] ("Overview",""),Space,Str "(",Code ("",[],[]) "https://github.com/mgylling/epub-testsuite/wiki/Overview",Str ")",Space,Str "for",Space,Str "additional",Space,Str "information."] ,RawBlock (Format "html") "
" ,RawBlock (Format "html") "
" ,Header 2 ("",[],[]) [Str "Conventions"] @@ -430,13 +430,13 @@ ,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 [RawInline (Format "html") "",Strong [Str "Lorem",Space,Str "Ipsum"],Space,RawInline (Format "html") "",Str "(",RawInline (Format "html") "",RawInline (Format "html") "",Str "Lorem",Space,Str "Ipsum",RawInline (Format "html") "",RawInline (Format "html") "",Str ")",RawInline (Format "html") "",RawInline (Format "html") ""] -,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"] ("#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"] ("#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."] ,RawBlock (Format "html") "
" ,RawBlock (Format "html") "
" ,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 [RawInline (Format "html") "",Strong [Str "Lorem",Space,Str "Ipsum"],Space,RawInline (Format "html") "",Str "(",RawInline (Format "html") "",RawInline (Format "html") "",Str "Lorem",Space,Str "Ipsum",RawInline (Format "html") "",RawInline (Format "html") "",Str ")",RawInline (Format "html") "",RawInline (Format "html") ""] -,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"] ("#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"] ("#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."] ,RawBlock (Format "html") "
" ,RawBlock (Format "html") "
" ,Header 2 ("",[],[]) [Span ("",["nature"],[]) [Str "[REQUIRED]"],Space,Span ("",["test-id"],[]) [Str "style-412"],Space,Code ("",[],[]) "inter-character"] diff --git a/tests/epub/wasteland.native b/tests/epub/wasteland.native index d931eec32..c2e18e082 100644 --- a/tests/epub/wasteland.native +++ b/tests/epub/wasteland.native @@ -6,4 +6,4 @@ ,RawBlock (Format "html") "
" ,Header 2 ("",[],[]) [Str "I.",Space,Str "THE",Space,Str "BURIAL",Space,Str "OF",Space,Str "THE",Space,Str "DEAD"] ,Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "April",Space,Str "is",Space,Str "the",Space,Str "cruellest",Space,Str "month,",Space,Str "breeding"]],Div ("",[],[]) [Plain [Str "Lilacs",Space,Str "out",Space,Str "of",Space,Str "the",Space,Str "dead",Space,Str "land,",Space,Str "mixing"]],Div ("",[],[]) [Plain [Str "Memory",Space,Str "and",Space,Str "desire,",Space,Str "stirring"]],Div ("",[],[]) [Plain [Str "Dull",Space,Str "roots",Space,Str "with",Space,Str "spring",Space,Str "rain."]],Div ("",[],[]) [Plain [Str "Winter",Space,Str "kept",Space,Str "us",Space,Str "warm,",Space,Str "covering"]],Div ("",[],[]) [Plain [Str "Earth",Space,Str "in",Space,Str "forgetful",Space,Str "snow,",Space,Str "feeding"]],Div ("",[],[]) [Plain [Str "A",Space,Str "little",Space,Str "life",Space,Str "with",Space,Str "dried",Space,Str "tubers."]],Div ("",[],[]) [Plain [Str "Summer",Space,Str "surprised",Space,Str "us,",Space,Str "coming",Space,Str "over",Space,Str "the",Space,Str "Starnbergersee"]],Div ("",[],[]) [Plain [Str "With",Space,Str "a",Space,Str "shower",Space,Str "of",Space,Str "rain;",Space,Str "we",Space,Str "stopped",Space,Str "in",Space,Str "the",Space,Str "colonnade,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "went",Space,Str "on",Space,Str "in",Space,Str "sunlight,",Space,Str "into",Space,Str "the",Space,Str "Hofgarten,",Span ("",["lnum"],[]) [Str "10"]]],Div ("",[],[]) [Plain [Str "And",Space,Str "drank",Space,Str "coffee,",Space,Str "and",Space,Str "talked",Space,Str "for",Space,Str "an",Space,Str "hour."]],Div ("",[],[("lang","de")]) [Plain [Str "Bin",Space,Str "gar",Space,Str "keine",Space,Str "Russin,",Space,Str "stamm'",Space,Str "aus",Space,Str "Litauen,",Space,Str "echt",Space,Str "deutsch."]],Div ("",[],[]) [Plain [Str "And",Space,Str "when",Space,Str "we",Space,Str "were",Space,Str "children,",Space,Str "staying",Space,Str "at",Space,Str "the",Space,Str "archduke's,"]],Div ("",[],[]) [Plain [Str "My",Space,Str "cousin's,",Space,Str "he",Space,Str "took",Space,Str "me",Space,Str "out",Space,Str "on",Space,Str "a",Space,Str "sled,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "I",Space,Str "was",Space,Str "frightened.",Space,Str "He",Space,Str "said,",Space,Str "Marie,"]],Div ("",[],[]) [Plain [Str "Marie,",Space,Str "hold",Space,Str "on",Space,Str "tight.",Space,Str "And",Space,Str "down",Space,Str "we",Space,Str "went."]],Div ("",[],[]) [Plain [Str "In",Space,Str "the",Space,Str "mountains,",Space,Str "there",Space,Str "you",Space,Str "feel",Space,Str "free."]],Div ("",[],[]) [Plain [Str "I",Space,Str "read,",Space,Str "much",Space,Str "of",Space,Str "the",Space,Str "night,",Space,Str "and",Space,Str "go",Space,Str "south",Space,Str "in",Space,Str "the",Space,Str "winter."]]] -,Div ("",["linegroup"],[]) [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"]],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."]]],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"]],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,"]],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."]]],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"]],Div ("",[],[]) [Plain [Str "There",Space,Str "is",Space,Str "shadow",Space,Str "under",Space,Str "this",Space,Str "red",Space,Str "rock,"]],Div ("",[],[]) [Plain [Str "(Come",Space,Str "in",Space,Str "under",Space,Str "the",Space,Str "shadow",Space,Str "of",Space,Str "this",Space,Str "red",Space,Str "rock),"]],Div ("",[],[]) [Plain [Str "And",Space,Str "I",Space,Str "will",Space,Str "show",Space,Str "you",Space,Str "something",Space,Str "different",Space,Str "from",Space,Str "either"]],Div ("",[],[]) [Plain [Str "Your",Space,Str "shadow",Space,Str "at",Space,Str "morning",Space,Str "striding",Space,Str "behind",Space,Str "you"]],Div ("",[],[]) [Plain [Str "Or",Space,Str "your",Space,Str "shadow",Space,Str "at",Space,Str "evening",Space,Str "rising",Space,Str "to",Space,Str "meet",Space,Str "you;"]],Div ("",[],[]) [Plain [Str "I",Space,Str "will",Space,Str "show",Space,Str "you",Space,Str "fear",Space,Str "in",Space,Str "a",Space,Str "handful",Space,Str "of",Space,Str "dust.",Span ("",["lnum"],[]) [Str "30"]]],BlockQuote [Div ("",[],[]) [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."]]],Div ("",[],[]) [Plain [Str "Der",Space,Str "Heimat",Space,Str "zu"]],Div ("",[],[]) [Plain [Str "Mein",Space,Str "Irisch",Space,Str "Kind,"]],Div ("",[],[]) [Plain [Str "Wo",Space,Str "weilest",Space,Str "du?"]]],RawBlock (Format "html") "",Div ("",[],[]) [Plain [Str "\"You",Space,Str "gave",Space,Str "me",Space,Str "hyacinths",Space,Str "first",Space,Str "a",Space,Str "year",Space,Str "ago;"]],Div ("",[],[]) [Plain [Str "\"They",Space,Str "called",Space,Str "me",Space,Str "the",Space,Str "hyacinth",Space,Str "girl.\""]],Div ("",[],[]) [Plain [Str "\8213Yet",Space,Str "when",Space,Str "we",Space,Str "came",Space,Str "back,",Space,Str "late,",Space,Str "from",Space,Str "the",Space,Str "Hyacinth",Space,Str "garden,"]],Div ("",[],[]) [Plain [Str "Your",Space,Str "arms",Space,Str "full,",Space,Str "and",Space,Str "your",Space,Str "hair",Space,Str "wet,",Space,Str "I",Space,Str "could",Space,Str "not"]],Div ("",[],[]) [Plain [Str "Speak,",Space,Str "and",Space,Str "my",Space,Str "eyes",Space,Str "failed,",Space,Str "I",Space,Str "was",Space,Str "neither"]],Div ("",[],[]) [Plain [Str "Living",Space,Str "nor",Space,Str "dead,",Space,Str "and",Space,Str "I",Space,Str "knew",Space,Str "nothing,",Span ("",["lnum"],[]) [Str "40"]]],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."]],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."]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "Madame",Space,Str "Sosostris,",Space,Str "famous",Space,Str "clairvoyante,"]],Div ("",[],[]) [Plain [Str "Had",Space,Str "a",Space,Str "bad",Space,Str "cold,",Space,Str "nevertheless"]],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,"]],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."]]],Div ("",[],[]) [Plain [Str "Is",Space,Str "your",Space,Str "card,",Space,Str "the",Space,Str "drowned",Space,Str "Phoenician",Space,Str "Sailor,"]],Div ("",[],[]) [Plain [Str "(Those",Space,Str "are",Space,Str "pearls",Space,Str "that",Space,Str "were",Space,Str "his",Space,Str "eyes.",Space,Str "Look!)"]],Div ("",[],[]) [Plain [Str "Here",Space,Str "is",Space,Str "Belladonna,",Space,Str "the",Space,Str "Lady",Space,Str "of",Space,Str "the",Space,Str "Rocks,"]],Div ("",[],[]) [Plain [Str "The",Space,Str "lady",Space,Str "of",Space,Str "situations.",Span ("",["lnum"],[]) [Str "50"]]],Div ("",[],[]) [Plain [Str "Here",Space,Str "is",Space,Str "the",Space,Str "man",Space,Str "with",Space,Str "three",Space,Str "staves,",Space,Str "and",Space,Str "here",Space,Str "the",Space,Str "Wheel,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "here",Space,Str "is",Space,Str "the",Space,Str "one-eyed",Space,Str "merchant,",Space,Str "and",Space,Str "this",Space,Str "card,"]],Div ("",[],[]) [Plain [Str "Which",Space,Str "is",Space,Str "blank,",Space,Str "is",Space,Str "something",Space,Str "he",Space,Str "carries",Space,Str "on",Space,Str "his",Space,Str "back,"]],Div ("",[],[]) [Plain [Str "Which",Space,Str "I",Space,Str "am",Space,Str "forbidden",Space,Str "to",Space,Str "see.",Space,Str "I",Space,Str "do",Space,Str "not",Space,Str "find"]],Div ("",[],[]) [Plain [Str "The",Space,Str "Hanged",Space,Str "Man.",Space,Str "Fear",Space,Str "death",Space,Str "by",Space,Str "water."]],Div ("",[],[]) [Plain [Str "I",Space,Str "see",Space,Str "crowds",Space,Str "of",Space,Str "people,",Space,Str "walking",Space,Str "round",Space,Str "in",Space,Str "a",Space,Str "ring."]],Div ("",[],[]) [Plain [Str "Thank",Space,Str "you.",Space,Str "If",Space,Str "you",Space,Str "see",Space,Str "dear",Space,Str "Mrs.",Space,Str "Equitone,"]],Div ("",[],[]) [Plain [Str "Tell",Space,Str "her",Space,Str "I",Space,Str "bring",Space,Str "the",Space,Str "horoscope",Space,Str "myself:"]],Div ("",[],[]) [Plain [Str "One",Space,Str "must",Space,Str "be",Space,Str "so",Space,Str "careful",Space,Str "these",Space,Str "days."]]],Div ("",["linegroup"],[]) [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.\""]]]],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,"]],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,"]],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.\""]]]],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.\""]]]],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."]],Div ("",[],[]) [Plain [Str "Flowed",Space,Str "up",Space,Str "the",Space,Str "hill",Space,Str "and",Space,Str "down",Space,Str "King",Space,Str "William",Space,Str "Street,"]],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"]],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."]]],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!"]],Div ("",[],[]) [Plain [Str "\"You",Space,Str "who",Space,Str "were",Space,Str "with",Space,Str "me",Space,Str "in",Space,Str "the",Space,Str "ships",Space,Str "at",Space,Str "Mylae!",Span ("",["lnum"],[]) [Str "70"]]],Div ("",[],[]) [Plain [Str "\"That",Space,Str "corpse",Space,Str "you",Space,Str "planted",Space,Str "last",Space,Str "year",Space,Str "in",Space,Str "your",Space,Str "garden,"]],Div ("",[],[]) [Plain [Str "\"Has",Space,Str "it",Space,Str "begun",Space,Str "to",Space,Str "sprout?",Space,Str "Will",Space,Str "it",Space,Str "bloom",Space,Str "this",Space,Str "year?"]],Div ("",[],[]) [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 ("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 "."]]],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!"]],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."]]],RawBlock (Format "html") "
",Header 2 ("",[],[]) [Str "II.",Space,Str "A",Space,Str "GAME",Space,Str "OF",Space,Str "CHESS"],Div ("",["linegroup"],[]) [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."]]],Div ("",[],[]) [Plain [Str "Glowed",Space,Str "on",Space,Str "the",Space,Str "marble,",Space,Str "where",Space,Str "the",Space,Str "glass"]],Div ("",[],[]) [Plain [Str "Held",Space,Str "up",Space,Str "by",Space,Str "standards",Space,Str "wrought",Space,Str "with",Space,Str "fruited",Space,Str "vines"]],Div ("",[],[]) [Plain [Str "From",Space,Str "which",Space,Str "a",Space,Str "golden",Space,Str "Cupidon",Space,Str "peeped",Space,Str "out",Span ("",["lnum"],[]) [Str "80"]]],Div ("",[],[]) [Plain [Str "(Another",Space,Str "hid",Space,Str "his",Space,Str "eyes",Space,Str "behind",Space,Str "his",Space,Str "wing)"]],Div ("",[],[]) [Plain [Str "Doubled",Space,Str "the",Space,Str "flames",Space,Str "of",Space,Str "sevenbranched",Space,Str "candelabra"]],Div ("",[],[]) [Plain [Str "Reflecting",Space,Str "light",Space,Str "upon",Space,Str "the",Space,Str "table",Space,Str "as"]],Div ("",[],[]) [Plain [Str "The",Space,Str "glitter",Space,Str "of",Space,Str "her",Space,Str "jewels",Space,Str "rose",Space,Str "to",Space,Str "meet",Space,Str "it,"]],Div ("",[],[]) [Plain [Str "From",Space,Str "satin",Space,Str "cases",Space,Str "poured",Space,Str "in",Space,Str "rich",Space,Str "profusion;"]],Div ("",[],[]) [Plain [Str "In",Space,Str "vials",Space,Str "of",Space,Str "ivory",Space,Str "and",Space,Str "coloured",Space,Str "glass"]],Div ("",[],[]) [Plain [Str "Unstoppered,",Space,Str "lurked",Space,Str "her",Space,Str "strange",Space,Str "synthetic",Space,Str "perfumes,"]],Div ("",[],[]) [Plain [Str "Unguent,",Space,Str "powdered,",Space,Str "or",Space,Str "liquid",Space,Str "-",Space,Str "troubled,",Space,Str "confused"]],Div ("",[],[]) [Plain [Str "And",Space,Str "drowned",Space,Str "the",Space,Str "sense",Space,Str "in",Space,Str "odours;",Space,Str "stirred",Space,Str "by",Space,Str "the",Space,Str "air"]],Div ("",[],[]) [Plain [Str "That",Space,Str "freshened",Space,Str "from",Space,Str "the",Space,Str "window,",Space,Str "these",Space,Str "ascended",Span ("",["lnum"],[]) [Str "90"]]],Div ("",[],[]) [Plain [Str "In",Space,Str "fattening",Space,Str "the",Space,Str "prolonged",Space,Str "candle-flames,"]],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."]]]],Div ("",[],[]) [Plain [Str "Stirring",Space,Str "the",Space,Str "pattern",Space,Str "on",Space,Str "the",Space,Str "coffered",Space,Str "ceiling."]],Div ("",[],[]) [Plain [Str "Huge",Space,Str "sea-wood",Space,Str "fed",Space,Str "with",Space,Str "copper"]],Div ("",[],[]) [Plain [Str "Burned",Space,Str "green",Space,Str "and",Space,Str "orange,",Space,Str "framed",Space,Str "by",Space,Str "the",Space,Str "coloured",Space,Str "stone,"]],Div ("",[],[]) [Plain [Str "In",Space,Str "which",Space,Str "sad",Space,Str "light",Space,Str "a",Space,Str "carved",Space,Str "dolphin",Space,Str "swam."]],Div ("",[],[]) [Plain [Str "Above",Space,Str "the",Space,Str "antique",Space,Str "mantel",Space,Str "was",Space,Str "displayed"]],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."]]],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."]]],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."]]],Div ("",[],[]) [Plain [Str "Filled",Space,Str "all",Space,Str "the",Space,Str "desert",Space,Str "with",Space,Str "inviolable",Space,Str "voice"]],Div ("",[],[]) [Plain [Str "And",Space,Str "still",Space,Str "she",Space,Str "cried,",Space,Str "and",Space,Str "still",Space,Str "the",Space,Str "world",Space,Str "pursues,"]],Div ("",[],[]) [Plain [Str "\"Jug",Space,Str "Jug\"",Space,Str "to",Space,Str "dirty",Space,Str "ears."]],Div ("",[],[]) [Plain [Str "And",Space,Str "other",Space,Str "withered",Space,Str "stumps",Space,Str "of",Space,Str "time"]],Div ("",[],[]) [Plain [Str "Were",Space,Str "told",Space,Str "upon",Space,Str "the",Space,Str "walls;",Space,Str "staring",Space,Str "forms"]],Div ("",[],[]) [Plain [Str "Leaned",Space,Str "out,",Space,Str "leaning,",Space,Str "hushing",Space,Str "the",Space,Str "room",Space,Str "enclosed."]],Div ("",[],[]) [Plain [Str "Footsteps",Space,Str "shuffled",Space,Str "on",Space,Str "the",Space,Str "stair."]],Div ("",[],[]) [Plain [Str "Under",Space,Str "the",Space,Str "firelight,",Space,Str "under",Space,Str "the",Space,Str "brush,",Space,Str "her",Space,Str "hair"]],Div ("",[],[]) [Plain [Str "Spread",Space,Str "out",Space,Str "in",Space,Str "fiery",Space,Str "points"]],Div ("",[],[]) [Plain [Str "Glowed",Space,Str "into",Space,Str "words,",Space,Str "then",Space,Str "would",Space,Str "be",Space,Str "savagely",Space,Str "still.",Span ("",["lnum"],[]) [Str "110"]]]],Div ("",["linegroup"],[]) [Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "\"My",Space,Str "nerves",Space,Str "are",Space,Str "bad",Space,Str "to-night.",Space,Str "Yes,",Space,Str "bad.",Space,Str "Stay",Space,Str "with",Space,Str "me."]],Div ("",[],[]) [Plain [Str "\"Speak",Space,Str "to",Space,Str "me.",Space,Str "Why",Space,Str "do",Space,Str "you",Space,Str "never",Space,Str "speak.",Space,Str "Speak."]],Div ("",[],[]) [Plain [Str "\"What",Space,Str "are",Space,Str "you",Space,Str "thinking",Space,Str "of?",Space,Str "What",Space,Str "thinking?",Space,Str "What?"]],Div ("",[],[]) [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 ("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."]]],Div ("",[],[]) [Plain [Str "Where",Space,Str "the",Space,Str "dead",Space,Str "men",Space,Str "lost",Space,Str "their",Space,Str "bones."]]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "\"What",Space,Str "is",Space,Str "that",Space,Str "noise?\""]],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?\""]]]],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?\""]],Div ("",["indent"],[]) [Plain [Str "Nothing",Space,Str "again",Space,Str "nothing.",Span ("",["lnum"],[]) [Str "120"]]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "\"Do"]],Div ("",[],[]) [Plain [Str "\"You",Space,Str "know",Space,Str "nothing?",Space,Str "Do",Space,Str "you",Space,Str "see",Space,Str "nothing?",Space,Str "Do",Space,Str "you",Space,Str "remember"]],Div ("",[],[]) [Plain [Str "\"Nothing?\""]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "I",Space,Str "remember"]],Div ("",[],[]) [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",[],[]) [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 ("",[],[]) [Plain [Str "But"]],Div ("",[],[]) [Plain [Str "O",Space,Str "O",Space,Str "O",Space,Str "O",Space,Str "that",Space,Str "Shakespeherian",Space,Str "Rag\8213"]],Div ("",[],[]) [Plain [Str "It's",Space,Str "so",Space,Str "elegant"]],Div ("",[],[]) [Plain [Str "So",Space,Str "intelligent",Span ("",["lnum"],[]) [Str "130"]]],Div ("",[],[]) [Plain [Str "\"What",Space,Str "shall",Space,Str "I",Space,Str "do",Space,Str "now?",Space,Str "What",Space,Str "shall",Space,Str "I",Space,Str "do?\""]],Div ("",[],[]) [Plain [Str "I",Space,Str "shall",Space,Str "rush",Space,Str "out",Space,Str "as",Space,Str "I",Space,Str "am,",Space,Str "and",Space,Str "walk",Space,Str "the",Space,Str "street"]],Div ("",[],[]) [Plain [Str "\"With",Space,Str "my",Space,Str "hair",Space,Str "down,",Space,Str "so.",Space,Str "What",Space,Str "shall",Space,Str "we",Space,Str "do",Space,Str "to-morrow?"]],Div ("",[],[]) [Plain [Str "\"What",Space,Str "shall",Space,Str "we",Space,Str "ever",Space,Str "do?\""]],Div ("",[],[]) [Plain [Str "The",Space,Str "hot",Space,Str "water",Space,Str "at",Space,Str "ten."]],Div ("",[],[]) [Plain [Str "And",Space,Str "if",Space,Str "it",Space,Str "rains,",Space,Str "a",Space,Str "closed",Space,Str "car",Space,Str "at",Space,Str "four."]],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,"]],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."]]],Div ("",["linegroup"],[]) [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 "-"]],Div ("",[],[]) [Plain [Str "I",Space,Str "didn't",Space,Str "mince",Space,Str "my",Space,Str "words,",Space,Str "I",Space,Str "said",Space,Str "to",Space,Str "her",Space,Str "myself,",Span ("",["lnum"],[]) [Str "140"]]],Div ("",[],[]) [Plain [Str "HURRY",Space,Str "UP",Space,Str "PLEASE",Space,Str "ITS",Space,Str "TIME"]],Div ("",[],[]) [Plain [Str "Now",Space,Str "Albert's",Space,Str "coming",Space,Str "back,",Space,Str "make",Space,Str "yourself",Space,Str "a",Space,Str "bit",Space,Str "smart."]],Div ("",[],[]) [Plain [Str "He'll",Space,Str "want",Space,Str "to",Space,Str "know",Space,Str "what",Space,Str "you",Space,Str "done",Space,Str "with",Space,Str "that",Space,Str "money",Space,Str "he",Space,Str "gave",Space,Str "you"]],Div ("",[],[]) [Plain [Str "To",Space,Str "get",Space,Str "yourself",Space,Str "some",Space,Str "teeth.",Space,Str "He",Space,Str "did,",Space,Str "I",Space,Str "was",Space,Str "there."]],Div ("",[],[]) [Plain [Str "You",Space,Str "have",Space,Str "them",Space,Str "all",Space,Str "out,",Space,Str "Lil,",Space,Str "and",Space,Str "get",Space,Str "a",Space,Str "nice",Space,Str "set,"]],Div ("",[],[]) [Plain [Str "He",Space,Str "said,",Space,Str "I",Space,Str "swear,",Space,Str "I",Space,Str "can't",Space,Str "bear",Space,Str "to",Space,Str "look",Space,Str "at",Space,Str "you."]],Div ("",[],[]) [Plain [Str "And",Space,Str "no",Space,Str "more",Space,Str "can't",Space,Str "I,",Space,Str "I",Space,Str "said,",Space,Str "and",Space,Str "think",Space,Str "of",Space,Str "poor",Space,Str "Albert,"]],Div ("",[],[]) [Plain [Str "He's",Space,Str "been",Space,Str "in",Space,Str "the",Space,Str "army",Space,Str "four",Space,Str "years,",Space,Str "he",Space,Str "wants",Space,Str "a",Space,Str "good",Space,Str "time,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "if",Space,Str "you",Space,Str "don't",Space,Str "give",Space,Str "it",Space,Str "him,",Space,Str "there's",Space,Str "others",Space,Str "will,",Space,Str "I",Space,Str "said."]],Div ("",[],[]) [Plain [Str "Oh",Space,Str "is",Space,Str "there,",Space,Str "she",Space,Str "said.",Space,Str "Something",Space,Str "o'",Space,Str "that,",Space,Str "I",Space,Str "said.",Span ("",["lnum"],[]) [Str "150"]]],Div ("",[],[]) [Plain [Str "Then",Space,Str "I'll",Space,Str "know",Space,Str "who",Space,Str "to",Space,Str "thank,",Space,Str "she",Space,Str "said,",Space,Str "and",Space,Str "give",Space,Str "me",Space,Str "a",Space,Str "straight",Space,Str "look."]],Div ("",[],[]) [Plain [Str "HURRY",Space,Str "UP",Space,Str "PLEASE",Space,Str "ITS",Space,Str "TIME"]],Div ("",[],[]) [Plain [Str "If",Space,Str "you",Space,Str "don't",Space,Str "like",Space,Str "it",Space,Str "you",Space,Str "can",Space,Str "get",Space,Str "on",Space,Str "with",Space,Str "it,",Space,Str "I",Space,Str "said."]],Div ("",[],[]) [Plain [Str "Others",Space,Str "can",Space,Str "pick",Space,Str "and",Space,Str "choose",Space,Str "if",Space,Str "you",Space,Str "can't."]],Div ("",[],[]) [Plain [Str "But",Space,Str "if",Space,Str "Albert",Space,Str "makes",Space,Str "off,",Space,Str "it",Space,Str "won't",Space,Str "be",Space,Str "for",Space,Str "lack",Space,Str "of",Space,Str "telling."]],Div ("",[],[]) [Plain [Str "You",Space,Str "ought",Space,Str "to",Space,Str "be",Space,Str "ashamed,",Space,Str "I",Space,Str "said,",Space,Str "to",Space,Str "look",Space,Str "so",Space,Str "antique."]],Div ("",[],[]) [Plain [Str "(And",Space,Str "her",Space,Str "only",Space,Str "thirty-one.)"]],Div ("",[],[]) [Plain [Str "I",Space,Str "can't",Space,Str "help",Space,Str "it,",Space,Str "she",Space,Str "said,",Space,Str "pulling",Space,Str "a",Space,Str "long",Space,Str "face,"]],Div ("",[],[]) [Plain [Str "It's",Space,Str "them",Space,Str "pills",Space,Str "I",Space,Str "took,",Space,Str "to",Space,Str "bring",Space,Str "it",Space,Str "off,",Space,Str "she",Space,Str "said."]],Div ("",[],[]) [Plain [Str "(She's",Space,Str "had",Space,Str "five",Space,Str "already,",Space,Str "and",Space,Str "nearly",Space,Str "died",Space,Str "of",Space,Str "young",Space,Str "George.)",Span ("",["lnum"],[]) [Str "160"]]],Div ("",[],[]) [Plain [Str "The",Space,Str "chemist",Space,Str "said",Space,Str "it",Space,Str "would",Space,Str "be",Space,Str "all",Space,Str "right,",Space,Str "but",Space,Str "I've",Space,Str "never",Space,Str "been",Space,Str "the",Space,Str "same."]],Div ("",[],[]) [Plain [Str "You",Space,Emph [Str "are"],Space,Str "a",Space,Str "proper",Space,Str "fool,",Space,Str "I",Space,Str "said."]],Div ("",[],[]) [Plain [Str "Well,",Space,Str "if",Space,Str "Albert",Space,Str "won't",Space,Str "leave",Space,Str "you",Space,Str "alone,",Space,Str "there",Space,Str "it",Space,Str "is,",Space,Str "I",Space,Str "said,"]],Div ("",[],[]) [Plain [Str "What",Space,Str "you",Space,Str "get",Space,Str "married",Space,Str "for",Space,Str "if",Space,Str "you",Space,Str "don't",Space,Str "want",Space,Str "children?"]],Div ("",[],[]) [Plain [Str "HURRY",Space,Str "UP",Space,Str "PLEASE",Space,Str "ITS",Space,Str "TIME"]],Div ("",[],[]) [Plain [Str "Well,",Space,Str "that",Space,Str "Sunday",Space,Str "Albert",Space,Str "was",Space,Str "home,",Space,Str "they",Space,Str "had",Space,Str "a",Space,Str "hot",Space,Str "gammon,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "they",Space,Str "asked",Space,Str "me",Space,Str "in",Space,Str "to",Space,Str "dinner,",Space,Str "to",Space,Str "get",Space,Str "the",Space,Str "beauty",Space,Str "of",Space,Str "it",Space,Str "hot\8213"]],Div ("",[],[]) [Plain [Str "HURRY",Space,Str "UP",Space,Str "PLEASE",Space,Str "ITS",Space,Str "TIME"]],Div ("",[],[]) [Plain [Str "HURRY",Space,Str "UP",Space,Str "PLEASE",Space,Str "ITS",Space,Str "TIME"]],Div ("",[],[]) [Plain [Str "Goonight",Space,Str "Bill.",Space,Str "Goonight",Space,Str "Lou.",Space,Str "Goonight",Space,Str "May.",Space,Str "Goonight.",Span ("",["lnum"],[]) [Str "170"]]],Div ("",[],[]) [Plain [Str "Ta",Space,Str "ta.",Space,Str "Goonight.",Space,Str "Goonight."]],Div ("",[],[]) [Plain [Str "Good",Space,Str "night,",Space,Str "ladies,",Space,Str "good",Space,Str "night,",Space,Str "sweet",Space,Str "ladies,",Space,Str "good",Space,Str "night,",Space,Str "good",Space,Str "night."]]],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 2 ("",[],[]) [Str "III.",Space,Str "THE",Space,Str "FIRE",Space,Str "SERMON"],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "The",Space,Str "river's",Space,Str "tent",Space,Str "is",Space,Str "broken:",Space,Str "the",Space,Str "last",Space,Str "fingers",Space,Str "of",Space,Str "leaf"]],Div ("",[],[]) [Plain [Str "Clutch",Space,Str "and",Space,Str "sink",Space,Str "into",Space,Str "the",Space,Str "wet",Space,Str "bank.",Space,Str "The",Space,Str "wind"]],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."]],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."]]],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,"]],Div ("",[],[]) [Plain [Str "Silk",Space,Str "handkerchiefs,",Space,Str "cardboard",Space,Str "boxes,",Space,Str "cigarette",Space,Str "ends"]],Div ("",[],[]) [Plain [Str "Or",Space,Str "other",Space,Str "testimony",Space,Str "of",Space,Str "summer",Space,Str "nights.",Space,Str "The",Space,Str "nymphs",Space,Str "are",Space,Str "departed."]],Div ("",[],[]) [Plain [Str "And",Space,Str "their",Space,Str "friends,",Space,Str "the",Space,Str "loitering",Space,Str "heirs",Space,Str "of",Space,Str "city",Space,Str "directors;",Span ("",["lnum"],[]) [Str "180"]]],Div ("",[],[]) [Plain [Str "Departed,",Space,Str "have",Space,Str "left",Space,Str "no",Space,Str "addresses."]],Div ("",[],[]) [Plain [Str "By",Space,Str "the",Space,Str "waters",Space,Str "of",Space,Str "Leman",Space,Str "I",Space,Str "sat",Space,Str "down",Space,Str "and",Space,Str "wept",Space,Str ".",Space,Str ".",Space,Str "."]],Div ("",[],[]) [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,"]],Div ("",[],[]) [Plain [Str "Sweet",Space,Str "Thames,",Space,Str "run",Space,Str "softly,",Space,Str "for",Space,Str "I",Space,Str "speak",Space,Str "not",Space,Str "loud",Space,Str "or",Space,Str "long."]],Div ("",[],[]) [Plain [Str "But",Space,Str "at",Space,Str "my",Space,Str "back",Space,Str "in",Space,Str "a",Space,Str "cold",Space,Str "blast",Space,Str "I",Space,Str "hear"]],Div ("",[],[]) [Plain [Str "The",Space,Str "rattle",Space,Str "of",Space,Str "the",Space,Str "bones,",Space,Str "and",Space,Str "chuckle",Space,Str "spread",Space,Str "from",Space,Str "ear",Space,Str "to",Space,Str "ear."]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "A",Space,Str "rat",Space,Str "crept",Space,Str "softly",Space,Str "through",Space,Str "the",Space,Str "vegetation"]],Div ("",[],[]) [Plain [Str "Dragging",Space,Str "its",Space,Str "slimy",Space,Str "belly",Space,Str "on",Space,Str "the",Space,Str "bank"]],Div ("",[],[]) [Plain [Str "While",Space,Str "I",Space,Str "was",Space,Str "fishing",Space,Str "in",Space,Str "the",Space,Str "dull",Space,Str "canal"]],Div ("",[],[]) [Plain [Str "On",Space,Str "a",Space,Str "winter",Space,Str "evening",Space,Str "round",Space,Str "behind",Space,Str "the",Space,Str "gashouse",Span ("",["lnum"],[]) [Str "190"]]],Div ("",[],[]) [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",[],[]) [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 ("",[],[]) [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 ("",[],[]) [Plain [Str "And",Space,Str "bones",Space,Str "cast",Space,Str "in",Space,Str "a",Space,Str "little",Space,Str "low",Space,Str "dry",Space,Str "garret,"]],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."]],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."]]],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 ".\""]]]]]],Div ("",[],[]) [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",[],[]) [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 ("",[],[]) [Plain [Str "And",Space,Str "on",Space,Str "her",Space,Str "daughter",Span ("",["lnum"],[]) [Str "200"]]],Div ("",[],[]) [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")]) [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 ("",[],[]) [Plain [Str "Twit",Space,Str "twit",Space,Str "twit"]],Div ("",[],[]) [Plain [Str "Jug",Space,Str "jug",Space,Str "jug",Space,Str "jug",Space,Str "jug",Space,Str "jug"]],Div ("",[],[]) [Plain [Str "So",Space,Str "rudely",Space,Str "forc'd."]],Div ("",[],[]) [Plain [Str "Tereu"]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "Unreal",Space,Str "City"]],Div ("",[],[]) [Plain [Str "Under",Space,Str "the",Space,Str "brown",Space,Str "fog",Space,Str "of",Space,Str "a",Space,Str "winter",Space,Str "noon"]],Div ("",[],[]) [Plain [Str "Mr.",Space,Str "Eugenides,",Space,Str "the",Space,Str "Smyrna",Space,Str "merchant"]],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."]]],Div ("",[],[]) [Plain [Str "C.i.f.",Space,Str "London:",Space,Str "documents",Space,Str "at",Space,Str "sight,"]],Div ("",[],[]) [Plain [Str "Asked",Space,Str "me",Space,Str "in",Space,Str "demotic",Space,Str "French"]],Div ("",[],[]) [Plain [Str "To",Space,Str "luncheon",Space,Str "at",Space,Str "the",Space,Str "Cannon",Space,Str "Street",Space,Str "Hotel"]],Div ("",[],[]) [Plain [Str "Followed",Space,Str "by",Space,Str "a",Space,Str "weekend",Space,Str "at",Space,Str "the",Space,Str "Metropole."]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "At",Space,Str "the",Space,Str "violet",Space,Str "hour,",Space,Str "when",Space,Str "the",Space,Str "eyes",Space,Str "and",Space,Str "back"]],Div ("",[],[]) [Plain [Str "Turn",Space,Str "upward",Space,Str "from",Space,Str "the",Space,Str "desk,",Space,Str "when",Space,Str "the",Space,Str "human",Space,Str "engine",Space,Str "waits"]],Div ("",[],[]) [Plain [Str "Like",Space,Str "a",Space,Str "taxi",Space,Str "throbbing",Space,Str "waiting,"]],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]]]],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"]],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"]]],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."]]],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"]],Div ("",[],[]) [Plain [Str "Her",Space,Str "stove,",Space,Str "and",Space,Str "lays",Space,Str "out",Space,Str "food",Space,Str "in",Space,Str "tins."]],Div ("",[],[]) [Plain [Str "Out",Space,Str "of",Space,Str "the",Space,Str "window",Space,Str "perilously",Space,Str "spread"]],Div ("",[],[]) [Plain [Str "Her",Space,Str "drying",Space,Str "combinations",Space,Str "touched",Space,Str "by",Space,Str "the",Space,Str "sun's",Space,Str "last",Space,Str "rays,"]],Div ("",[],[]) [Plain [Str "On",Space,Str "the",Space,Str "divan",Space,Str "are",Space,Str "piled",Space,Str "(at",Space,Str "night",Space,Str "her",Space,Str "bed)"]],Div ("",[],[]) [Plain [Str "Stockings,",Space,Str "slippers,",Space,Str "camisoles,",Space,Str "and",Space,Str "stays."]],Div ("",[],[]) [Plain [Str "I",Space,Str "Tiresias,",Space,Str "old",Space,Str "man",Space,Str "with",Space,Str "wrinkled",Space,Str "dugs"]],Div ("",[],[]) [Plain [Str "Perceived",Space,Str "the",Space,Str "scene,",Space,Str "and",Space,Str "foretold",Space,Str "the",Space,Str "rest",Space,Str "-"]],Div ("",[],[]) [Plain [Str "I",Space,Str "too",Space,Str "awaited",Space,Str "the",Space,Str "expected",Space,Str "guest.",Span ("",["lnum"],[]) [Str "230"]]],Div ("",[],[]) [Plain [Str "He,",Space,Str "the",Space,Str "young",Space,Str "man",Space,Str "carbuncular,",Space,Str "arrives,"]],Div ("",[],[]) [Plain [Str "A",Space,Str "small",Space,Str "house",Space,Str "agent's",Space,Str "clerk,",Space,Str "with",Space,Str "one",Space,Str "bold",Space,Str "stare,"]],Div ("",[],[]) [Plain [Str "One",Space,Str "of",Space,Str "the",Space,Str "low",Space,Str "on",Space,Str "whom",Space,Str "assurance",Space,Str "sits"]],Div ("",[],[]) [Plain [Str "As",Space,Str "a",Space,Str "silk",Space,Str "hat",Space,Str "on",Space,Str "a",Space,Str "Bradford",Space,Str "millionaire."]],Div ("",[],[]) [Plain [Str "The",Space,Str "time",Space,Str "is",Space,Str "now",Space,Str "propitious,",Space,Str "as",Space,Str "he",Space,Str "guesses,"]],Div ("",[],[]) [Plain [Str "The",Space,Str "meal",Space,Str "is",Space,Str "ended,",Space,Str "she",Space,Str "is",Space,Str "bored",Space,Str "and",Space,Str "tired,"]],Div ("",[],[]) [Plain [Str "Endeavours",Space,Str "to",Space,Str "engage",Space,Str "her",Space,Str "in",Space,Str "caresses"]],Div ("",[],[]) [Plain [Str "Which",Space,Str "still",Space,Str "are",Space,Str "unreproved,",Space,Str "if",Space,Str "undesired."]],Div ("",[],[]) [Plain [Str "Flushed",Space,Str "and",Space,Str "decided,",Space,Str "he",Space,Str "assaults",Space,Str "at",Space,Str "once;"]],Div ("",[],[]) [Plain [Str "Exploring",Space,Str "hands",Space,Str "encounter",Space,Str "no",Space,Str "defence;",Span ("",["lnum"],[]) [Str "240"]]],Div ("",[],[]) [Plain [Str "His",Space,Str "vanity",Space,Str "requires",Space,Str "no",Space,Str "response,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "makes",Space,Str "a",Space,Str "welcome",Space,Str "of",Space,Str "indifference."]],Div ("",[],[]) [Plain [Str "(And",Space,Str "I",Space,Str "Tiresias",Space,Str "have",Space,Str "foresuffered",Space,Str "all"]],Div ("",[],[]) [Plain [Str "Enacted",Space,Str "on",Space,Str "this",Space,Str "same",Space,Str "divan",Space,Str "or",Space,Str "bed;"]],Div ("",[],[]) [Plain [Str "I",Space,Str "who",Space,Str "have",Space,Str "sat",Space,Str "by",Space,Str "Thebes",Space,Str "below",Space,Str "the",Space,Str "wall"]],Div ("",[],[]) [Plain [Str "And",Space,Str "walked",Space,Str "among",Space,Str "the",Space,Str "lowest",Space,Str "of",Space,Str "the",Space,Str "dead.)"]],Div ("",[],[]) [Plain [Str "Bestows",Space,Str "one",Space,Str "final",Space,Str "patronising",Space,Str "kiss,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "gropes",Space,Str "his",Space,Str "way,",Space,Str "finding",Space,Str "the",Space,Str "stairs",Space,Str "unlit",Space,Str ".",Space,Str ".",Space,Str "."]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "She",Space,Str "turns",Space,Str "and",Space,Str "looks",Space,Str "a",Space,Str "moment",Space,Str "in",Space,Str "the",Space,Str "glass,"]],Div ("",[],[]) [Plain [Str "Hardly",Space,Str "aware",Space,Str "of",Space,Str "her",Space,Str "departed",Space,Str "lover;",Span ("",["lnum"],[]) [Str "250"]]],Div ("",[],[]) [Plain [Str "Her",Space,Str "brain",Space,Str "allows",Space,Str "one",Space,Str "half-formed",Space,Str "thought",Space,Str "to",Space,Str "pass:"]],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.\""]],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."]]],Div ("",[],[]) [Plain [Str "Paces",Space,Str "about",Space,Str "her",Space,Str "room",Space,Str "again,",Space,Str "alone,"]],Div ("",[],[]) [Plain [Str "She",Space,Str "smoothes",Space,Str "her",Space,Str "hair",Space,Str "with",Space,Str "automatic",Space,Str "hand,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "puts",Space,Str "a",Space,Str "record",Space,Str "on",Space,Str "the",Space,Str "gramophone."]]],Div ("",["linegroup"],[]) [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."]]],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."]],Div ("",[],[]) [Plain [Str "O",Space,Str "City",Space,Str "city,",Space,Str "I",Space,Str "can",Space,Str "sometimes",Space,Str "hear"]],Div ("",[],[]) [Plain [Str "Beside",Space,Str "a",Space,Str "public",Space,Str "bar",Space,Str "in",Space,Str "Lower",Space,Str "Thames",Space,Str "Street,",Span ("",["lnum"],[]) [Str "260"]]],Div ("",[],[]) [Plain [Str "The",Space,Str "pleasant",Space,Str "whining",Space,Str "of",Space,Str "a",Space,Str "mandoline"]],Div ("",[],[]) [Plain [Str "And",Space,Str "a",Space,Str "clatter",Space,Str "and",Space,Str "a",Space,Str "chatter",Space,Str "from",Space,Str "within"]],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"]],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.)."]]],Div ("",[],[]) [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 ("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."]]],Div ("",[],[]) [Plain [Str "Oil",Space,Str "and",Space,Str "tar"]],Div ("",[],[]) [Plain [Str "The",Space,Str "barges",Space,Str "drift"]],Div ("",[],[]) [Plain [Str "With",Space,Str "the",Space,Str "turning",Space,Str "tide"]],Div ("",[],[]) [Plain [Str "Red",Space,Str "sails",Span ("",["lnum"],[]) [Str "270"]]],Div ("",[],[]) [Plain [Str "Wide"]],Div ("",[],[]) [Plain [Str "To",Space,Str "leeward,",Space,Str "swing",Space,Str "on",Space,Str "the",Space,Str "heavy",Space,Str "spar."]],Div ("",[],[]) [Plain [Str "The",Space,Str "barges",Space,Str "wash"]],Div ("",[],[]) [Plain [Str "Drifting",Space,Str "logs"]],Div ("",[],[]) [Plain [Str "Down",Space,Str "Greenwich",Space,Str "reach"]],Div ("",[],[]) [Plain [Str "Past",Space,Str "the",Space,Str "Isle",Space,Str "of",Space,Str "Dogs."]],Div ("",["indent"],[]) [Plain [Str "Weialala",Space,Str "leia"]],Div ("",["indent"],[]) [Plain [Str "Wallala",Space,Str "leialala"]]],Div ("",["linegroup","indent"],[]) [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.\""]]]]]],Div ("",[],[]) [Plain [Str "Beating",Space,Str "oars",Span ("",["lnum"],[]) [Str "280"]]],Div ("",[],[]) [Plain [Str "The",Space,Str "stern",Space,Str "was",Space,Str "formed"]],Div ("",[],[]) [Plain [Str "A",Space,Str "gilded",Space,Str "shell"]],Div ("",[],[]) [Plain [Str "Red",Space,Str "and",Space,Str "gold"]],Div ("",[],[]) [Plain [Str "The",Space,Str "brisk",Space,Str "swell"]],Div ("",[],[]) [Plain [Str "Rippled",Space,Str "both",Space,Str "shores"]],Div ("",[],[]) [Plain [Str "Southwest",Space,Str "wind"]],Div ("",[],[]) [Plain [Str "Carried",Space,Str "down",Space,Str "stream"]],Div ("",[],[]) [Plain [Str "The",Space,Str "peal",Space,Str "of",Space,Str "bells"]],Div ("",[],[]) [Plain [Str "White",Space,Str "towers"]],Div ("",["indent"],[]) [Plain [Str "Weialala",Space,Str "leia",Span ("",["lnum"],[]) [Str "290"]]],Div ("",["indent"],[]) [Plain [Str "Wallala",Space,Str "leialala"]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "\"Trams",Space,Str "and",Space,Str "dusty",Space,Str "trees."]],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.\""]]]],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"]],Div ("",[],[]) [Plain [Str "Supine",Space,Str "on",Space,Str "the",Space,Str "floor",Space,Str "of",Space,Str "a",Space,Str "narrow",Space,Str "canoe.\""]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "\"My",Space,Str "feet",Space,Str "are",Space,Str "at",Space,Str "Moorgate,",Space,Str "and",Space,Str "my",Space,Str "heart"]],Div ("",[],[]) [Plain [Str "Under",Space,Str "my",Space,Str "feet.",Space,Str "After",Space,Str "the",Space,Str "event"]],Div ("",[],[]) [Plain [Str "He",Space,Str "wept.",Space,Str "He",Space,Str "promised",Space,Str "'a",Space,Str "new",Space,Str "start'."]],Div ("",[],[]) [Plain [Str "I",Space,Str "made",Space,Str "no",Space,Str "comment.",Space,Str "What",Space,Str "should",Space,Str "I",Space,Str "resent?\""]],Div ("",[],[]) [Plain [Str "\"On",Space,Str "Margate",Space,Str "Sands.",Span ("",["lnum"],[]) [Str "300"]]],Div ("",[],[]) [Plain [Str "I",Space,Str "can",Space,Str "connect"]],Div ("",[],[]) [Plain [Str "Nothing",Space,Str "with",Space,Str "nothing."]],Div ("",[],[]) [Plain [Str "The",Space,Str "broken",Space,Str "fingernails",Space,Str "of",Space,Str "dirty",Space,Str "hands."]],Div ("",[],[]) [Plain [Str "My",Space,Str "people",Space,Str "humble",Space,Str "people",Space,Str "who",Space,Str "expect"]],Div ("",[],[]) [Plain [Str "Nothing.\""]],Div ("",["indent"],[]) [Plain [Str "la",Space,Str "la"]]],Div ("",["linegroup"],[]) [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.\""]]],Div ("",["linegroup"],[]) [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."]]],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."]]],Div ("",[],[]) [Plain [Str "O",Space,Str "Lord",Space,Str "Thou",Space,Str "pluckest",Span ("",["lnum"],[]) [Str "310"]]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "burning"]]],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 2 ("",[],[]) [Str "IV.",Space,Str "DEATH",Space,Str "BY",Space,Str "WATER"],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "Phlebas",Space,Str "the",Space,Str "Phoenician,",Space,Str "a",Space,Str "fortnight",Space,Str "dead,"]],Div ("",[],[]) [Plain [Str "Forgot",Space,Str "the",Space,Str "cry",Space,Str "of",Space,Str "gulls,",Space,Str "and",Space,Str "the",Space,Str "deep",Space,Str "sea",Space,Str "swell"]],Div ("",[],[]) [Plain [Str "And",Space,Str "the",Space,Str "profit",Space,Str "and",Space,Str "loss."]]],Div ("",["linegroup"],[]) [Div ("",["indent2"],[]) [Plain [Str "A",Space,Str "current",Space,Str "under",Space,Str "sea"]],Div ("",[],[]) [Plain [Str "Picked",Space,Str "his",Space,Str "bones",Space,Str "in",Space,Str "whispers.",Space,Str "As",Space,Str "he",Space,Str "rose",Space,Str "and",Space,Str "fell"]],Div ("",[],[]) [Plain [Str "He",Space,Str "passed",Space,Str "the",Space,Str "stages",Space,Str "of",Space,Str "his",Space,Str "age",Space,Str "and",Space,Str "youth"]],Div ("",[],[]) [Plain [Str "Entering",Space,Str "the",Space,Str "whirlpool."]]],Div ("",["linegroup"],[]) [Div ("",["indent2"],[]) [Plain [Str "Gentile",Space,Str "or",Space,Str "Jew"]],Div ("",[],[]) [Plain [Str "O",Space,Str "you",Space,Str "who",Space,Str "turn",Space,Str "the",Space,Str "wheel",Space,Str "and",Space,Str "look",Space,Str "to",Space,Str "windward,",Span ("",["lnum"],[]) [Str "320"]]],Div ("",[],[]) [Plain [Str "Consider",Space,Str "Phlebas,",Space,Str "who",Space,Str "was",Space,Str "once",Space,Str "handsome",Space,Str "and",Space,Str "tall",Space,Str "as",Space,Str "you."]]],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 2 ("",[],[]) [Str "V.",Space,Str "WHAT",Space,Str "THE",Space,Str "THUNDER",Space,Str "SAID"],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "After",Space,Str "the",Space,Str "torchlight",Space,Str "red",Space,Str "on",Space,Str "sweaty",Space,Str "faces"]],Div ("",[],[]) [Plain [Str "After",Space,Str "the",Space,Str "frosty",Space,Str "silence",Space,Str "in",Space,Str "the",Space,Str "gardens"]],Div ("",[],[]) [Plain [Str "After",Space,Str "the",Space,Str "agony",Space,Str "in",Space,Str "stony",Space,Str "places"]],Div ("",[],[]) [Plain [Str "The",Space,Str "shouting",Space,Str "and",Space,Str "the",Space,Str "crying"]],Div ("",[],[]) [Plain [Str "Prison",Space,Str "and",Space,Str "palace",Space,Str "and",Space,Str "reverberation"]],Div ("",[],[]) [Plain [Str "Of",Space,Str "thunder",Space,Str "of",Space,Str "spring",Space,Str "over",Space,Str "distant",Space,Str "mountains"]],Div ("",[],[]) [Plain [Str "He",Space,Str "who",Space,Str "was",Space,Str "living",Space,Str "is",Space,Str "now",Space,Str "dead"]],Div ("",[],[]) [Plain [Str "We",Space,Str "who",Space,Str "were",Space,Str "living",Space,Str "are",Space,Str "now",Space,Str "dying"]],Div ("",[],[]) [Plain [Str "With",Space,Str "a",Space,Str "little",Space,Str "patience",Span ("",["lnum"],[]) [Str "330"]]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "Here",Space,Str "is",Space,Str "no",Space,Str "water",Space,Str "but",Space,Str "only",Space,Str "rock"]],Div ("",[],[]) [Plain [Str "Rock",Space,Str "and",Space,Str "no",Space,Str "water",Space,Str "and",Space,Str "the",Space,Str "sandy",Space,Str "road"]],Div ("",[],[]) [Plain [Str "The",Space,Str "road",Space,Str "winding",Space,Str "above",Space,Str "among",Space,Str "the",Space,Str "mountains"]],Div ("",[],[]) [Plain [Str "Which",Space,Str "are",Space,Str "mountains",Space,Str "of",Space,Str "rock",Space,Str "without",Space,Str "water"]],Div ("",[],[]) [Plain [Str "If",Space,Str "there",Space,Str "were",Space,Str "water",Space,Str "we",Space,Str "should",Space,Str "stop",Space,Str "and",Space,Str "drink"]],Div ("",[],[]) [Plain [Str "Amongst",Space,Str "the",Space,Str "rock",Space,Str "one",Space,Str "cannot",Space,Str "stop",Space,Str "or",Space,Str "think"]],Div ("",[],[]) [Plain [Str "Sweat",Space,Str "is",Space,Str "dry",Space,Str "and",Space,Str "feet",Space,Str "are",Space,Str "in",Space,Str "the",Space,Str "sand"]],Div ("",[],[]) [Plain [Str "If",Space,Str "there",Space,Str "were",Space,Str "only",Space,Str "water",Space,Str "amongst",Space,Str "the",Space,Str "rock"]],Div ("",[],[]) [Plain [Str "Dead",Space,Str "mountain",Space,Str "mouth",Space,Str "of",Space,Str "carious",Space,Str "teeth",Space,Str "that",Space,Str "cannot",Space,Str "spit"]],Div ("",[],[]) [Plain [Str "Here",Space,Str "one",Space,Str "can",Space,Str "neither",Space,Str "stand",Space,Str "nor",Space,Str "lie",Space,Str "nor",Space,Str "sit",Span ("",["lnum"],[]) [Str "340"]]],Div ("",[],[]) [Plain [Str "There",Space,Str "is",Space,Str "not",Space,Str "even",Space,Str "silence",Space,Str "in",Space,Str "the",Space,Str "mountains"]],Div ("",[],[]) [Plain [Str "But",Space,Str "dry",Space,Str "sterile",Space,Str "thunder",Space,Str "without",Space,Str "rain"]],Div ("",[],[]) [Plain [Str "There",Space,Str "is",Space,Str "not",Space,Str "even",Space,Str "solitude",Space,Str "in",Space,Str "the",Space,Str "mountains"]],Div ("",[],[]) [Plain [Str "But",Space,Str "red",Space,Str "sullen",Space,Str "faces",Space,Str "sneer",Space,Str "and",Space,Str "snarl"]],Div ("",[],[]) [Plain [Str "From",Space,Str "doors",Space,Str "of",Space,Str "mudcracked",Space,Str "houses"]],Div ("",["linegroup"],[]) [Div ("",["indent2"],[]) [Plain [Str "If",Space,Str "there",Space,Str "were",Space,Str "water"]],Div ("",[],[]) [Plain [Str "And",Space,Str "no",Space,Str "rock"]],Div ("",[],[]) [Plain [Str "If",Space,Str "there",Space,Str "were",Space,Str "rock"]],Div ("",[],[]) [Plain [Str "And",Space,Str "also",Space,Str "water"]],Div ("",[],[]) [Plain [Str "And",Space,Str "water",Span ("",["lnum"],[]) [Str "350"]]],Div ("",[],[]) [Plain [Str "A",Space,Str "spring"]],Div ("",[],[]) [Plain [Str "A",Space,Str "pool",Space,Str "among",Space,Str "the",Space,Str "rock"]],Div ("",[],[]) [Plain [Str "If",Space,Str "there",Space,Str "were",Space,Str "the",Space,Str "sound",Space,Str "of",Space,Str "water",Space,Str "only"]],Div ("",[],[]) [Plain [Str "Not",Space,Str "the",Space,Str "cicada"]],Div ("",[],[]) [Plain [Str "And",Space,Str "dry",Space,Str "grass",Space,Str "singing"]],Div ("",[],[]) [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",[],[]) [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 ("",[],[]) [Plain [Str "Drip",Space,Str "drop",Space,Str "drip",Space,Str "drop",Space,Str "drop",Space,Str "drop",Space,Str "drop"]],Div ("",[],[]) [Plain [Str "But",Space,Str "there",Space,Str "is",Space,Str "no",Space,Str "water"]]]],Div ("",["linegroup"],[]) [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."]]],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"]],Div ("",[],[]) [Plain [Str "But",Space,Str "when",Space,Str "I",Space,Str "look",Space,Str "ahead",Space,Str "up",Space,Str "the",Space,Str "white",Space,Str "road"]],Div ("",[],[]) [Plain [Str "There",Space,Str "is",Space,Str "always",Space,Str "another",Space,Str "one",Space,Str "walking",Space,Str "beside",Space,Str "you"]],Div ("",[],[]) [Plain [Str "Gliding",Space,Str "wrapt",Space,Str "in",Space,Str "a",Space,Str "brown",Space,Str "mantle,",Space,Str "hooded"]],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"]],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.\""]]]],Div ("",["linegroup"],[]) [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"]],Div ("",[],[]) [Plain [Str "Murmur",Space,Str "of",Space,Str "maternal",Space,Str "lamentation"]],Div ("",[],[]) [Plain [Str "Who",Space,Str "are",Space,Str "those",Space,Str "hooded",Space,Str "hordes",Space,Str "swarming"]],Div ("",[],[]) [Plain [Str "Over",Space,Str "endless",Space,Str "plains,",Space,Str "stumbling",Space,Str "in",Space,Str "cracked",Space,Str "earth",Span ("",["lnum"],[]) [Str "370"]]],Div ("",[],[]) [Plain [Str "Ringed",Space,Str "by",Space,Str "the",Space,Str "flat",Space,Str "horizon",Space,Str "only"]],Div ("",[],[]) [Plain [Str "What",Space,Str "is",Space,Str "the",Space,Str "city",Space,Str "over",Space,Str "the",Space,Str "mountains"]],Div ("",[],[]) [Plain [Str "Cracks",Space,Str "and",Space,Str "reforms",Space,Str "and",Space,Str "bursts",Space,Str "in",Space,Str "the",Space,Str "violet",Space,Str "air"]],Div ("",[],[]) [Plain [Str "Falling",Space,Str "towers"]],Div ("",[],[]) [Plain [Str "Jerusalem",Space,Str "Athens",Space,Str "Alexandria"]],Div ("",[],[]) [Plain [Str "Vienna",Space,Str "London"]],Div ("",[],[]) [Plain [Str "Unreal"]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "A",Space,Str "woman",Space,Str "drew",Space,Str "her",Space,Str "long",Space,Str "black",Space,Str "hair",Space,Str "out",Space,Str "tight"]],Div ("",[],[]) [Plain [Str "And",Space,Str "fiddled",Space,Str "whisper",Space,Str "music",Space,Str "on",Space,Str "those",Space,Str "strings"]],Div ("",[],[]) [Plain [Str "And",Space,Str "bats",Space,Str "with",Space,Str "baby",Space,Str "faces",Space,Str "in",Space,Str "the",Space,Str "violet",Space,Str "light",Span ("",["lnum"],[]) [Str "380"]]],Div ("",[],[]) [Plain [Str "Whistled,",Space,Str "and",Space,Str "beat",Space,Str "their",Space,Str "wings"]],Div ("",[],[]) [Plain [Str "And",Space,Str "crawled",Space,Str "head",Space,Str "downward",Space,Str "down",Space,Str "a",Space,Str "blackened",Space,Str "wall"]],Div ("",[],[]) [Plain [Str "And",Space,Str "upside",Space,Str "down",Space,Str "in",Space,Str "air",Space,Str "were",Space,Str "towers"]],Div ("",[],[]) [Plain [Str "Tolling",Space,Str "reminiscent",Space,Str "bells,",Space,Str "that",Space,Str "kept",Space,Str "the",Space,Str "hours"]],Div ("",[],[]) [Plain [Str "And",Space,Str "voices",Space,Str "singing",Space,Str "out",Space,Str "of",Space,Str "empty",Space,Str "cisterns",Space,Str "and",Space,Str "exhausted",Space,Str "wells."]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "In",Space,Str "this",Space,Str "decayed",Space,Str "hole",Space,Str "among",Space,Str "the",Space,Str "mountains"]],Div ("",[],[]) [Plain [Str "In",Space,Str "the",Space,Str "faint",Space,Str "moonlight,",Space,Str "the",Space,Str "grass",Space,Str "is",Space,Str "singing"]],Div ("",[],[]) [Plain [Str "Over",Space,Str "the",Space,Str "tumbled",Space,Str "graves,",Space,Str "about",Space,Str "the",Space,Str "chapel"]],Div ("",[],[]) [Plain [Str "There",Space,Str "is",Space,Str "the",Space,Str "empty",Space,Str "chapel,",Space,Str "only",Space,Str "the",Space,Str "wind's",Space,Str "home."]],Div ("",[],[]) [Plain [Str "It",Space,Str "has",Space,Str "no",Space,Str "windows,",Space,Str "and",Space,Str "the",Space,Str "door",Space,Str "swings,",Span ("",["lnum"],[]) [Str "390"]]],Div ("",[],[]) [Plain [Str "Dry",Space,Str "bones",Space,Str "can",Space,Str "harm",Space,Str "no",Space,Str "one."]],Div ("",[],[]) [Plain [Str "Only",Space,Str "a",Space,Str "cock",Space,Str "stood",Space,Str "on",Space,Str "the",Space,Str "rooftree"]],Div ("",[],[]) [Plain [Str "Co",Space,Str "co",Space,Str "rico",Space,Str "co",Space,Str "co",Space,Str "rico"]],Div ("",[],[]) [Plain [Str "In",Space,Str "a",Space,Str "flash",Space,Str "of",Space,Str "lightning.",Space,Str "Then",Space,Str "a",Space,Str "damp",Space,Str "gust"]],Div ("",[],[]) [Plain [Str "Bringing",Space,Str "rain"]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "Ganga",Space,Str "was",Space,Str "sunken,",Space,Str "and",Space,Str "the",Space,Str "limp",Space,Str "leaves"]],Div ("",[],[]) [Plain [Str "Waited",Space,Str "for",Space,Str "rain,",Space,Str "while",Space,Str "the",Space,Str "black",Space,Str "clouds"]],Div ("",[],[]) [Plain [Str "Gathered",Space,Str "far",Space,Str "distant,",Space,Str "over",Space,Str "Himavant."]],Div ("",[],[]) [Plain [Str "The",Space,Str "jungle",Space,Str "crouched,",Space,Str "humped",Space,Str "in",Space,Str "silence."]],Div ("",[],[]) [Plain [Str "Then",Space,Str "spoke",Space,Str "the",Space,Str "thunder",Span ("",["lnum"],[]) [Str "400"]]],Div ("",[],[]) [Plain [Str "DA"]],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."]]],Div ("",[],[]) [Plain [Str "My",Space,Str "friend,",Space,Str "blood",Space,Str "shaking",Space,Str "my",Space,Str "heart"]],Div ("",[],[]) [Plain [Str "The",Space,Str "awful",Space,Str "daring",Space,Str "of",Space,Str "a",Space,Str "moment's",Space,Str "surrender"]],Div ("",[],[]) [Plain [Str "Which",Space,Str "an",Space,Str "age",Space,Str "of",Space,Str "prudence",Space,Str "can",Space,Str "never",Space,Str "retract"]],Div ("",[],[]) [Plain [Str "By",Space,Str "this,",Space,Str "and",Space,Str "this",Space,Str "only,",Space,Str "we",Space,Str "have",Space,Str "existed"]],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"]],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.\""]]]],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"]],Div ("",[],[]) [Plain [Str "In",Space,Str "our",Space,Str "empty",Space,Str "rooms",Span ("",["lnum"],[]) [Str "410"]]],Div ("",[],[]) [Plain [Str "DA"]],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.\""]]]],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"]],Div ("",[],[]) [Plain [Str "We",Space,Str "think",Space,Str "of",Space,Str "the",Space,Str "key,",Space,Str "each",Space,Str "in",Space,Str "his",Space,Str "prison"]],Div ("",[],[]) [Plain [Str "Thinking",Space,Str "of",Space,Str "the",Space,Str "key,",Space,Str "each",Space,Str "confirms",Space,Str "a",Space,Str "prison"]],Div ("",[],[]) [Plain [Str "Only",Space,Str "at",Space,Str "nightfall,",Space,Str "aetherial",Space,Str "rumours"]],Div ("",[],[]) [Plain [Str "Revive",Space,Str "for",Space,Str "a",Space,Str "moment",Space,Str "a",Space,Str "broken",Space,Str "Coriolanus"]],Div ("",[],[]) [Plain [Str "DA"]],Div ("",[],[]) [Plain [Span ("",[],[("lang","sa")]) [Str "Damyata"],Str ":",Space,Str "The",Space,Str "boat",Space,Str "responded"]],Div ("",[],[]) [Plain [Str "Gaily,",Space,Str "to",Space,Str "the",Space,Str "hand",Space,Str "expert",Space,Str "with",Space,Str "sail",Space,Str "and",Space,Str "oar",Span ("",["lnum"],[]) [Str "420"]]],Div ("",[],[]) [Plain [Str "The",Space,Str "sea",Space,Str "was",Space,Str "calm,",Space,Str "your",Space,Str "heart",Space,Str "would",Space,Str "have",Space,Str "responded"]],Div ("",[],[]) [Plain [Str "Gaily,",Space,Str "when",Space,Str "invited,",Space,Str "beating",Space,Str "obedient"]],Div ("",[],[]) [Plain [Str "To",Space,Str "controlling",Space,Str "hands"]]],Div ("",["linegroup"],[]) [Div ("",["indent"],[]) [Plain [Str "I",Space,Str "sat",Space,Str "upon",Space,Str "the",Space,Str "shore"]],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."]]],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?"]],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"]],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.\""]]]],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."]]],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."]]],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"]],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."]]],Div ("",[],[("lang","sa")]) [Plain [Str "Datta.",Space,Str "Dayadhvam.",Space,Str "Damyata."]],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."]]]],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 2 ("",[],[]) [Str "NOTES",Space,Str "ON",Space,Str "\"THE",Space,Str "WASTE",Space,Str "LAND\""],Para [Str "Not",Space,Str "only",Space,Str "the",Space,Str "title,",Space,Str "but",Space,Str "the",Space,Str "plan",Space,Str "and",Space,Str "a",Space,Str "good",Space,Str "deal",Space,Str "of",Space,Str "the",Space,Str "incidental",Space,Str "symbolism",Space,Str "of",Space,Str "the",Space,Str "poem",Space,Str "were",Space,Str "suggested",Space,Str "by",Space,Str "Miss",Space,Str "Jessie",Space,Str "L.",Space,Str "Weston's",Space,Str "book",Space,Str "on",Space,Str "the",Space,Str "Grail",Space,Str "legend:",Space,Str "From",Space,Str "Ritual",Space,Str "to",Space,Str "Romance"],Para [Str "Indeed,",Space,Str "so",Space,Str "deeply",Space,Str "am",Space,Str "I",Space,Str "indebted,",Space,Str "Miss",Space,Str "Weston's",Space,Str "book",Space,Str "will",Space,Str "elucidate",Space,Str "the",Space,Str "difficulties",Space,Str "of",Space,Str "the",Space,Str "poem",Space,Str "much",Space,Str "better",Space,Str "than",Space,Str "my",Space,Str "notes",Space,Str "can",Space,Str "do;",Space,Str "and",Space,Str "I",Space,Str "recommend",Space,Str "it",Space,Str "(apart",Space,Str "from",Space,Str "the",Space,Str "great",Space,Str "interest",Space,Str "of",Space,Str "the",Space,Str "book",Space,Str "itself)",Space,Str "to",Space,Str "any",Space,Str "who",Space,Str "think",Space,Str "such",Space,Str "elucidation",Space,Str "of",Space,Str "the",Space,Str "poem",Space,Str "worth",Space,Str "the",Space,Str "trouble.",Space,Str "To",Space,Str "another",Space,Str "work",Space,Str "of",Space,Str "anthropology",Space,Str "I",Space,Str "am",Space,Str "indebted",Space,Str "in",Space,Str "general,",Space,Str "one",Space,Str "which",Space,Str "has",Space,Str "influenced",Space,Str "our",Space,Str "generation",Space,Str "profoundly;",Space,Str "I",Space,Str "mean",Space,Str "The",Space,Str "Golden",Space,Str "Bough;",Space,Str "I",Space,Str "have",Space,Str "used",Space,Str "especially",Space,Str "the",Space,Str "two",Space,Str "volumes",Space,Str "Adonis,",Space,Str "Attis,",Space,Str "Osiris.",Space,Str "Anyone",Space,Str "who",Space,Str "is",Space,Str "acquainted",Space,Str "with",Space,Str "these",Space,Str "works",Space,Str "will",Space,Str "immediately",Space,Str "recognise",Space,Str "in",Space,Str "the",Space,Str "poem",Space,Str "certain",Space,Str "references",Space,Str "to",Space,Str "vegetation",Space,Str "ceremonies."],RawBlock (Format "html") "
",Header 3 ("",[],[]) [Str "I.",Space,Str "THE",Space,Str "BURIAL",Space,Str "OF",Space,Str "THE",Space,Str "DEAD"],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 3 ("",[],[]) [Str "II.",Space,Str "A",Space,Str "GAME",Space,Str "OF",Space,Str "CHESS"],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 3 ("",[],[]) [Str "III.",Space,Str "THE",Space,Str "FIRE",Space,Str "SERMON"],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 3 ("",[],[]) [Str "V.",Space,Str "WHAT",Space,Str "THE",Space,Str "THUNDER",Space,Str "SAID"],Para [Str "In",Space,Str "the",Space,Str "first",Space,Str "part",Space,Str "of",Space,Str "Part",Space,Str "V",Space,Str "three",Space,Str "themes",Space,Str "are",Space,Str "employed:",Space,Str "the",Space,Str "journey",Space,Str "to",Space,Str "Emmaus,",Space,Str "the",Space,Str "approach",Space,Str "to",Space,Str "the",Space,Str "Chapel",Space,Str "Perilous",Space,Str "(see",Space,Str "Miss",Space,Str "Weston's",Space,Str "book)",Space,Str "and",Space,Str "the",Space,Str "present",Space,Str "decay",Space,Str "of",Space,Str "eastern",Space,Str "Europe."],RawBlock (Format "html") "
",RawBlock (Format "html") "
",RawBlock (Format "html") "
"]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]] +,Div ("",["linegroup"],[]) [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"]],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."]]],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"]],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,"]],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."]]],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"]],Div ("",[],[]) [Plain [Str "There",Space,Str "is",Space,Str "shadow",Space,Str "under",Space,Str "this",Space,Str "red",Space,Str "rock,"]],Div ("",[],[]) [Plain [Str "(Come",Space,Str "in",Space,Str "under",Space,Str "the",Space,Str "shadow",Space,Str "of",Space,Str "this",Space,Str "red",Space,Str "rock),"]],Div ("",[],[]) [Plain [Str "And",Space,Str "I",Space,Str "will",Space,Str "show",Space,Str "you",Space,Str "something",Space,Str "different",Space,Str "from",Space,Str "either"]],Div ("",[],[]) [Plain [Str "Your",Space,Str "shadow",Space,Str "at",Space,Str "morning",Space,Str "striding",Space,Str "behind",Space,Str "you"]],Div ("",[],[]) [Plain [Str "Or",Space,Str "your",Space,Str "shadow",Space,Str "at",Space,Str "evening",Space,Str "rising",Space,Str "to",Space,Str "meet",Space,Str "you;"]],Div ("",[],[]) [Plain [Str "I",Space,Str "will",Space,Str "show",Space,Str "you",Space,Str "fear",Space,Str "in",Space,Str "a",Space,Str "handful",Space,Str "of",Space,Str "dust.",Span ("",["lnum"],[]) [Str "30"]]],BlockQuote [Div ("",[],[]) [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."]]],Div ("",[],[]) [Plain [Str "Der",Space,Str "Heimat",Space,Str "zu"]],Div ("",[],[]) [Plain [Str "Mein",Space,Str "Irisch",Space,Str "Kind,"]],Div ("",[],[]) [Plain [Str "Wo",Space,Str "weilest",Space,Str "du?"]]],RawBlock (Format "html") "",Div ("",[],[]) [Plain [Str "\"You",Space,Str "gave",Space,Str "me",Space,Str "hyacinths",Space,Str "first",Space,Str "a",Space,Str "year",Space,Str "ago;"]],Div ("",[],[]) [Plain [Str "\"They",Space,Str "called",Space,Str "me",Space,Str "the",Space,Str "hyacinth",Space,Str "girl.\""]],Div ("",[],[]) [Plain [Str "\8213Yet",Space,Str "when",Space,Str "we",Space,Str "came",Space,Str "back,",Space,Str "late,",Space,Str "from",Space,Str "the",Space,Str "Hyacinth",Space,Str "garden,"]],Div ("",[],[]) [Plain [Str "Your",Space,Str "arms",Space,Str "full,",Space,Str "and",Space,Str "your",Space,Str "hair",Space,Str "wet,",Space,Str "I",Space,Str "could",Space,Str "not"]],Div ("",[],[]) [Plain [Str "Speak,",Space,Str "and",Space,Str "my",Space,Str "eyes",Space,Str "failed,",Space,Str "I",Space,Str "was",Space,Str "neither"]],Div ("",[],[]) [Plain [Str "Living",Space,Str "nor",Space,Str "dead,",Space,Str "and",Space,Str "I",Space,Str "knew",Space,Str "nothing,",Span ("",["lnum"],[]) [Str "40"]]],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."]],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."]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "Madame",Space,Str "Sosostris,",Space,Str "famous",Space,Str "clairvoyante,"]],Div ("",[],[]) [Plain [Str "Had",Space,Str "a",Space,Str "bad",Space,Str "cold,",Space,Str "nevertheless"]],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,"]],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."]]],Div ("",[],[]) [Plain [Str "Is",Space,Str "your",Space,Str "card,",Space,Str "the",Space,Str "drowned",Space,Str "Phoenician",Space,Str "Sailor,"]],Div ("",[],[]) [Plain [Str "(Those",Space,Str "are",Space,Str "pearls",Space,Str "that",Space,Str "were",Space,Str "his",Space,Str "eyes.",Space,Str "Look!)"]],Div ("",[],[]) [Plain [Str "Here",Space,Str "is",Space,Str "Belladonna,",Space,Str "the",Space,Str "Lady",Space,Str "of",Space,Str "the",Space,Str "Rocks,"]],Div ("",[],[]) [Plain [Str "The",Space,Str "lady",Space,Str "of",Space,Str "situations.",Span ("",["lnum"],[]) [Str "50"]]],Div ("",[],[]) [Plain [Str "Here",Space,Str "is",Space,Str "the",Space,Str "man",Space,Str "with",Space,Str "three",Space,Str "staves,",Space,Str "and",Space,Str "here",Space,Str "the",Space,Str "Wheel,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "here",Space,Str "is",Space,Str "the",Space,Str "one-eyed",Space,Str "merchant,",Space,Str "and",Space,Str "this",Space,Str "card,"]],Div ("",[],[]) [Plain [Str "Which",Space,Str "is",Space,Str "blank,",Space,Str "is",Space,Str "something",Space,Str "he",Space,Str "carries",Space,Str "on",Space,Str "his",Space,Str "back,"]],Div ("",[],[]) [Plain [Str "Which",Space,Str "I",Space,Str "am",Space,Str "forbidden",Space,Str "to",Space,Str "see.",Space,Str "I",Space,Str "do",Space,Str "not",Space,Str "find"]],Div ("",[],[]) [Plain [Str "The",Space,Str "Hanged",Space,Str "Man.",Space,Str "Fear",Space,Str "death",Space,Str "by",Space,Str "water."]],Div ("",[],[]) [Plain [Str "I",Space,Str "see",Space,Str "crowds",Space,Str "of",Space,Str "people,",Space,Str "walking",Space,Str "round",Space,Str "in",Space,Str "a",Space,Str "ring."]],Div ("",[],[]) [Plain [Str "Thank",Space,Str "you.",Space,Str "If",Space,Str "you",Space,Str "see",Space,Str "dear",Space,Str "Mrs.",Space,Str "Equitone,"]],Div ("",[],[]) [Plain [Str "Tell",Space,Str "her",Space,Str "I",Space,Str "bring",Space,Str "the",Space,Str "horoscope",Space,Str "myself:"]],Div ("",[],[]) [Plain [Str "One",Space,Str "must",Space,Str "be",Space,Str "so",Space,Str "careful",Space,Str "these",Space,Str "days."]]],Div ("",["linegroup"],[]) [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.\""]]]],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,"]],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,"]],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.\""]]]],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.\""]]]],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."]],Div ("",[],[]) [Plain [Str "Flowed",Space,Str "up",Space,Str "the",Space,Str "hill",Space,Str "and",Space,Str "down",Space,Str "King",Space,Str "William",Space,Str "Street,"]],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"]],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."]]],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!"]],Div ("",[],[]) [Plain [Str "\"You",Space,Str "who",Space,Str "were",Space,Str "with",Space,Str "me",Space,Str "in",Space,Str "the",Space,Str "ships",Space,Str "at",Space,Str "Mylae!",Span ("",["lnum"],[]) [Str "70"]]],Div ("",[],[]) [Plain [Str "\"That",Space,Str "corpse",Space,Str "you",Space,Str "planted",Space,Str "last",Space,Str "year",Space,Str "in",Space,Str "your",Space,Str "garden,"]],Div ("",[],[]) [Plain [Str "\"Has",Space,Str "it",Space,Str "begun",Space,Str "to",Space,Str "sprout?",Space,Str "Will",Space,Str "it",Space,Str "bloom",Space,Str "this",Space,Str "year?"]],Div ("",[],[]) [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 ("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 "."]]],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!"]],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."]]],RawBlock (Format "html") "
",Header 2 ("",[],[]) [Str "II.",Space,Str "A",Space,Str "GAME",Space,Str "OF",Space,Str "CHESS"],Div ("",["linegroup"],[]) [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."]]],Div ("",[],[]) [Plain [Str "Glowed",Space,Str "on",Space,Str "the",Space,Str "marble,",Space,Str "where",Space,Str "the",Space,Str "glass"]],Div ("",[],[]) [Plain [Str "Held",Space,Str "up",Space,Str "by",Space,Str "standards",Space,Str "wrought",Space,Str "with",Space,Str "fruited",Space,Str "vines"]],Div ("",[],[]) [Plain [Str "From",Space,Str "which",Space,Str "a",Space,Str "golden",Space,Str "Cupidon",Space,Str "peeped",Space,Str "out",Span ("",["lnum"],[]) [Str "80"]]],Div ("",[],[]) [Plain [Str "(Another",Space,Str "hid",Space,Str "his",Space,Str "eyes",Space,Str "behind",Space,Str "his",Space,Str "wing)"]],Div ("",[],[]) [Plain [Str "Doubled",Space,Str "the",Space,Str "flames",Space,Str "of",Space,Str "sevenbranched",Space,Str "candelabra"]],Div ("",[],[]) [Plain [Str "Reflecting",Space,Str "light",Space,Str "upon",Space,Str "the",Space,Str "table",Space,Str "as"]],Div ("",[],[]) [Plain [Str "The",Space,Str "glitter",Space,Str "of",Space,Str "her",Space,Str "jewels",Space,Str "rose",Space,Str "to",Space,Str "meet",Space,Str "it,"]],Div ("",[],[]) [Plain [Str "From",Space,Str "satin",Space,Str "cases",Space,Str "poured",Space,Str "in",Space,Str "rich",Space,Str "profusion;"]],Div ("",[],[]) [Plain [Str "In",Space,Str "vials",Space,Str "of",Space,Str "ivory",Space,Str "and",Space,Str "coloured",Space,Str "glass"]],Div ("",[],[]) [Plain [Str "Unstoppered,",Space,Str "lurked",Space,Str "her",Space,Str "strange",Space,Str "synthetic",Space,Str "perfumes,"]],Div ("",[],[]) [Plain [Str "Unguent,",Space,Str "powdered,",Space,Str "or",Space,Str "liquid",Space,Str "-",Space,Str "troubled,",Space,Str "confused"]],Div ("",[],[]) [Plain [Str "And",Space,Str "drowned",Space,Str "the",Space,Str "sense",Space,Str "in",Space,Str "odours;",Space,Str "stirred",Space,Str "by",Space,Str "the",Space,Str "air"]],Div ("",[],[]) [Plain [Str "That",Space,Str "freshened",Space,Str "from",Space,Str "the",Space,Str "window,",Space,Str "these",Space,Str "ascended",Span ("",["lnum"],[]) [Str "90"]]],Div ("",[],[]) [Plain [Str "In",Space,Str "fattening",Space,Str "the",Space,Str "prolonged",Space,Str "candle-flames,"]],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."]]]],Div ("",[],[]) [Plain [Str "Stirring",Space,Str "the",Space,Str "pattern",Space,Str "on",Space,Str "the",Space,Str "coffered",Space,Str "ceiling."]],Div ("",[],[]) [Plain [Str "Huge",Space,Str "sea-wood",Space,Str "fed",Space,Str "with",Space,Str "copper"]],Div ("",[],[]) [Plain [Str "Burned",Space,Str "green",Space,Str "and",Space,Str "orange,",Space,Str "framed",Space,Str "by",Space,Str "the",Space,Str "coloured",Space,Str "stone,"]],Div ("",[],[]) [Plain [Str "In",Space,Str "which",Space,Str "sad",Space,Str "light",Space,Str "a",Space,Str "carved",Space,Str "dolphin",Space,Str "swam."]],Div ("",[],[]) [Plain [Str "Above",Space,Str "the",Space,Str "antique",Space,Str "mantel",Space,Str "was",Space,Str "displayed"]],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."]]],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."]]],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."]]],Div ("",[],[]) [Plain [Str "Filled",Space,Str "all",Space,Str "the",Space,Str "desert",Space,Str "with",Space,Str "inviolable",Space,Str "voice"]],Div ("",[],[]) [Plain [Str "And",Space,Str "still",Space,Str "she",Space,Str "cried,",Space,Str "and",Space,Str "still",Space,Str "the",Space,Str "world",Space,Str "pursues,"]],Div ("",[],[]) [Plain [Str "\"Jug",Space,Str "Jug\"",Space,Str "to",Space,Str "dirty",Space,Str "ears."]],Div ("",[],[]) [Plain [Str "And",Space,Str "other",Space,Str "withered",Space,Str "stumps",Space,Str "of",Space,Str "time"]],Div ("",[],[]) [Plain [Str "Were",Space,Str "told",Space,Str "upon",Space,Str "the",Space,Str "walls;",Space,Str "staring",Space,Str "forms"]],Div ("",[],[]) [Plain [Str "Leaned",Space,Str "out,",Space,Str "leaning,",Space,Str "hushing",Space,Str "the",Space,Str "room",Space,Str "enclosed."]],Div ("",[],[]) [Plain [Str "Footsteps",Space,Str "shuffled",Space,Str "on",Space,Str "the",Space,Str "stair."]],Div ("",[],[]) [Plain [Str "Under",Space,Str "the",Space,Str "firelight,",Space,Str "under",Space,Str "the",Space,Str "brush,",Space,Str "her",Space,Str "hair"]],Div ("",[],[]) [Plain [Str "Spread",Space,Str "out",Space,Str "in",Space,Str "fiery",Space,Str "points"]],Div ("",[],[]) [Plain [Str "Glowed",Space,Str "into",Space,Str "words,",Space,Str "then",Space,Str "would",Space,Str "be",Space,Str "savagely",Space,Str "still.",Span ("",["lnum"],[]) [Str "110"]]]],Div ("",["linegroup"],[]) [Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "\"My",Space,Str "nerves",Space,Str "are",Space,Str "bad",Space,Str "to-night.",Space,Str "Yes,",Space,Str "bad.",Space,Str "Stay",Space,Str "with",Space,Str "me."]],Div ("",[],[]) [Plain [Str "\"Speak",Space,Str "to",Space,Str "me.",Space,Str "Why",Space,Str "do",Space,Str "you",Space,Str "never",Space,Str "speak.",Space,Str "Speak."]],Div ("",[],[]) [Plain [Str "\"What",Space,Str "are",Space,Str "you",Space,Str "thinking",Space,Str "of?",Space,Str "What",Space,Str "thinking?",Space,Str "What?"]],Div ("",[],[]) [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 ("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."]]],Div ("",[],[]) [Plain [Str "Where",Space,Str "the",Space,Str "dead",Space,Str "men",Space,Str "lost",Space,Str "their",Space,Str "bones."]]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "\"What",Space,Str "is",Space,Str "that",Space,Str "noise?\""]],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?\""]]]],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?\""]],Div ("",["indent"],[]) [Plain [Str "Nothing",Space,Str "again",Space,Str "nothing.",Span ("",["lnum"],[]) [Str "120"]]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "\"Do"]],Div ("",[],[]) [Plain [Str "\"You",Space,Str "know",Space,Str "nothing?",Space,Str "Do",Space,Str "you",Space,Str "see",Space,Str "nothing?",Space,Str "Do",Space,Str "you",Space,Str "remember"]],Div ("",[],[]) [Plain [Str "\"Nothing?\""]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "I",Space,Str "remember"]],Div ("",[],[]) [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",[],[]) [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 ("",[],[]) [Plain [Str "But"]],Div ("",[],[]) [Plain [Str "O",Space,Str "O",Space,Str "O",Space,Str "O",Space,Str "that",Space,Str "Shakespeherian",Space,Str "Rag\8213"]],Div ("",[],[]) [Plain [Str "It's",Space,Str "so",Space,Str "elegant"]],Div ("",[],[]) [Plain [Str "So",Space,Str "intelligent",Span ("",["lnum"],[]) [Str "130"]]],Div ("",[],[]) [Plain [Str "\"What",Space,Str "shall",Space,Str "I",Space,Str "do",Space,Str "now?",Space,Str "What",Space,Str "shall",Space,Str "I",Space,Str "do?\""]],Div ("",[],[]) [Plain [Str "I",Space,Str "shall",Space,Str "rush",Space,Str "out",Space,Str "as",Space,Str "I",Space,Str "am,",Space,Str "and",Space,Str "walk",Space,Str "the",Space,Str "street"]],Div ("",[],[]) [Plain [Str "\"With",Space,Str "my",Space,Str "hair",Space,Str "down,",Space,Str "so.",Space,Str "What",Space,Str "shall",Space,Str "we",Space,Str "do",Space,Str "to-morrow?"]],Div ("",[],[]) [Plain [Str "\"What",Space,Str "shall",Space,Str "we",Space,Str "ever",Space,Str "do?\""]],Div ("",[],[]) [Plain [Str "The",Space,Str "hot",Space,Str "water",Space,Str "at",Space,Str "ten."]],Div ("",[],[]) [Plain [Str "And",Space,Str "if",Space,Str "it",Space,Str "rains,",Space,Str "a",Space,Str "closed",Space,Str "car",Space,Str "at",Space,Str "four."]],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,"]],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."]]],Div ("",["linegroup"],[]) [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 "-"]],Div ("",[],[]) [Plain [Str "I",Space,Str "didn't",Space,Str "mince",Space,Str "my",Space,Str "words,",Space,Str "I",Space,Str "said",Space,Str "to",Space,Str "her",Space,Str "myself,",Span ("",["lnum"],[]) [Str "140"]]],Div ("",[],[]) [Plain [Str "HURRY",Space,Str "UP",Space,Str "PLEASE",Space,Str "ITS",Space,Str "TIME"]],Div ("",[],[]) [Plain [Str "Now",Space,Str "Albert's",Space,Str "coming",Space,Str "back,",Space,Str "make",Space,Str "yourself",Space,Str "a",Space,Str "bit",Space,Str "smart."]],Div ("",[],[]) [Plain [Str "He'll",Space,Str "want",Space,Str "to",Space,Str "know",Space,Str "what",Space,Str "you",Space,Str "done",Space,Str "with",Space,Str "that",Space,Str "money",Space,Str "he",Space,Str "gave",Space,Str "you"]],Div ("",[],[]) [Plain [Str "To",Space,Str "get",Space,Str "yourself",Space,Str "some",Space,Str "teeth.",Space,Str "He",Space,Str "did,",Space,Str "I",Space,Str "was",Space,Str "there."]],Div ("",[],[]) [Plain [Str "You",Space,Str "have",Space,Str "them",Space,Str "all",Space,Str "out,",Space,Str "Lil,",Space,Str "and",Space,Str "get",Space,Str "a",Space,Str "nice",Space,Str "set,"]],Div ("",[],[]) [Plain [Str "He",Space,Str "said,",Space,Str "I",Space,Str "swear,",Space,Str "I",Space,Str "can't",Space,Str "bear",Space,Str "to",Space,Str "look",Space,Str "at",Space,Str "you."]],Div ("",[],[]) [Plain [Str "And",Space,Str "no",Space,Str "more",Space,Str "can't",Space,Str "I,",Space,Str "I",Space,Str "said,",Space,Str "and",Space,Str "think",Space,Str "of",Space,Str "poor",Space,Str "Albert,"]],Div ("",[],[]) [Plain [Str "He's",Space,Str "been",Space,Str "in",Space,Str "the",Space,Str "army",Space,Str "four",Space,Str "years,",Space,Str "he",Space,Str "wants",Space,Str "a",Space,Str "good",Space,Str "time,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "if",Space,Str "you",Space,Str "don't",Space,Str "give",Space,Str "it",Space,Str "him,",Space,Str "there's",Space,Str "others",Space,Str "will,",Space,Str "I",Space,Str "said."]],Div ("",[],[]) [Plain [Str "Oh",Space,Str "is",Space,Str "there,",Space,Str "she",Space,Str "said.",Space,Str "Something",Space,Str "o'",Space,Str "that,",Space,Str "I",Space,Str "said.",Span ("",["lnum"],[]) [Str "150"]]],Div ("",[],[]) [Plain [Str "Then",Space,Str "I'll",Space,Str "know",Space,Str "who",Space,Str "to",Space,Str "thank,",Space,Str "she",Space,Str "said,",Space,Str "and",Space,Str "give",Space,Str "me",Space,Str "a",Space,Str "straight",Space,Str "look."]],Div ("",[],[]) [Plain [Str "HURRY",Space,Str "UP",Space,Str "PLEASE",Space,Str "ITS",Space,Str "TIME"]],Div ("",[],[]) [Plain [Str "If",Space,Str "you",Space,Str "don't",Space,Str "like",Space,Str "it",Space,Str "you",Space,Str "can",Space,Str "get",Space,Str "on",Space,Str "with",Space,Str "it,",Space,Str "I",Space,Str "said."]],Div ("",[],[]) [Plain [Str "Others",Space,Str "can",Space,Str "pick",Space,Str "and",Space,Str "choose",Space,Str "if",Space,Str "you",Space,Str "can't."]],Div ("",[],[]) [Plain [Str "But",Space,Str "if",Space,Str "Albert",Space,Str "makes",Space,Str "off,",Space,Str "it",Space,Str "won't",Space,Str "be",Space,Str "for",Space,Str "lack",Space,Str "of",Space,Str "telling."]],Div ("",[],[]) [Plain [Str "You",Space,Str "ought",Space,Str "to",Space,Str "be",Space,Str "ashamed,",Space,Str "I",Space,Str "said,",Space,Str "to",Space,Str "look",Space,Str "so",Space,Str "antique."]],Div ("",[],[]) [Plain [Str "(And",Space,Str "her",Space,Str "only",Space,Str "thirty-one.)"]],Div ("",[],[]) [Plain [Str "I",Space,Str "can't",Space,Str "help",Space,Str "it,",Space,Str "she",Space,Str "said,",Space,Str "pulling",Space,Str "a",Space,Str "long",Space,Str "face,"]],Div ("",[],[]) [Plain [Str "It's",Space,Str "them",Space,Str "pills",Space,Str "I",Space,Str "took,",Space,Str "to",Space,Str "bring",Space,Str "it",Space,Str "off,",Space,Str "she",Space,Str "said."]],Div ("",[],[]) [Plain [Str "(She's",Space,Str "had",Space,Str "five",Space,Str "already,",Space,Str "and",Space,Str "nearly",Space,Str "died",Space,Str "of",Space,Str "young",Space,Str "George.)",Span ("",["lnum"],[]) [Str "160"]]],Div ("",[],[]) [Plain [Str "The",Space,Str "chemist",Space,Str "said",Space,Str "it",Space,Str "would",Space,Str "be",Space,Str "all",Space,Str "right,",Space,Str "but",Space,Str "I've",Space,Str "never",Space,Str "been",Space,Str "the",Space,Str "same."]],Div ("",[],[]) [Plain [Str "You",Space,Emph [Str "are"],Space,Str "a",Space,Str "proper",Space,Str "fool,",Space,Str "I",Space,Str "said."]],Div ("",[],[]) [Plain [Str "Well,",Space,Str "if",Space,Str "Albert",Space,Str "won't",Space,Str "leave",Space,Str "you",Space,Str "alone,",Space,Str "there",Space,Str "it",Space,Str "is,",Space,Str "I",Space,Str "said,"]],Div ("",[],[]) [Plain [Str "What",Space,Str "you",Space,Str "get",Space,Str "married",Space,Str "for",Space,Str "if",Space,Str "you",Space,Str "don't",Space,Str "want",Space,Str "children?"]],Div ("",[],[]) [Plain [Str "HURRY",Space,Str "UP",Space,Str "PLEASE",Space,Str "ITS",Space,Str "TIME"]],Div ("",[],[]) [Plain [Str "Well,",Space,Str "that",Space,Str "Sunday",Space,Str "Albert",Space,Str "was",Space,Str "home,",Space,Str "they",Space,Str "had",Space,Str "a",Space,Str "hot",Space,Str "gammon,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "they",Space,Str "asked",Space,Str "me",Space,Str "in",Space,Str "to",Space,Str "dinner,",Space,Str "to",Space,Str "get",Space,Str "the",Space,Str "beauty",Space,Str "of",Space,Str "it",Space,Str "hot\8213"]],Div ("",[],[]) [Plain [Str "HURRY",Space,Str "UP",Space,Str "PLEASE",Space,Str "ITS",Space,Str "TIME"]],Div ("",[],[]) [Plain [Str "HURRY",Space,Str "UP",Space,Str "PLEASE",Space,Str "ITS",Space,Str "TIME"]],Div ("",[],[]) [Plain [Str "Goonight",Space,Str "Bill.",Space,Str "Goonight",Space,Str "Lou.",Space,Str "Goonight",Space,Str "May.",Space,Str "Goonight.",Span ("",["lnum"],[]) [Str "170"]]],Div ("",[],[]) [Plain [Str "Ta",Space,Str "ta.",Space,Str "Goonight.",Space,Str "Goonight."]],Div ("",[],[]) [Plain [Str "Good",Space,Str "night,",Space,Str "ladies,",Space,Str "good",Space,Str "night,",Space,Str "sweet",Space,Str "ladies,",Space,Str "good",Space,Str "night,",Space,Str "good",Space,Str "night."]]],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 2 ("",[],[]) [Str "III.",Space,Str "THE",Space,Str "FIRE",Space,Str "SERMON"],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "The",Space,Str "river's",Space,Str "tent",Space,Str "is",Space,Str "broken:",Space,Str "the",Space,Str "last",Space,Str "fingers",Space,Str "of",Space,Str "leaf"]],Div ("",[],[]) [Plain [Str "Clutch",Space,Str "and",Space,Str "sink",Space,Str "into",Space,Str "the",Space,Str "wet",Space,Str "bank.",Space,Str "The",Space,Str "wind"]],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."]],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."]]],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,"]],Div ("",[],[]) [Plain [Str "Silk",Space,Str "handkerchiefs,",Space,Str "cardboard",Space,Str "boxes,",Space,Str "cigarette",Space,Str "ends"]],Div ("",[],[]) [Plain [Str "Or",Space,Str "other",Space,Str "testimony",Space,Str "of",Space,Str "summer",Space,Str "nights.",Space,Str "The",Space,Str "nymphs",Space,Str "are",Space,Str "departed."]],Div ("",[],[]) [Plain [Str "And",Space,Str "their",Space,Str "friends,",Space,Str "the",Space,Str "loitering",Space,Str "heirs",Space,Str "of",Space,Str "city",Space,Str "directors;",Span ("",["lnum"],[]) [Str "180"]]],Div ("",[],[]) [Plain [Str "Departed,",Space,Str "have",Space,Str "left",Space,Str "no",Space,Str "addresses."]],Div ("",[],[]) [Plain [Str "By",Space,Str "the",Space,Str "waters",Space,Str "of",Space,Str "Leman",Space,Str "I",Space,Str "sat",Space,Str "down",Space,Str "and",Space,Str "wept",Space,Str ".",Space,Str ".",Space,Str "."]],Div ("",[],[]) [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,"]],Div ("",[],[]) [Plain [Str "Sweet",Space,Str "Thames,",Space,Str "run",Space,Str "softly,",Space,Str "for",Space,Str "I",Space,Str "speak",Space,Str "not",Space,Str "loud",Space,Str "or",Space,Str "long."]],Div ("",[],[]) [Plain [Str "But",Space,Str "at",Space,Str "my",Space,Str "back",Space,Str "in",Space,Str "a",Space,Str "cold",Space,Str "blast",Space,Str "I",Space,Str "hear"]],Div ("",[],[]) [Plain [Str "The",Space,Str "rattle",Space,Str "of",Space,Str "the",Space,Str "bones,",Space,Str "and",Space,Str "chuckle",Space,Str "spread",Space,Str "from",Space,Str "ear",Space,Str "to",Space,Str "ear."]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "A",Space,Str "rat",Space,Str "crept",Space,Str "softly",Space,Str "through",Space,Str "the",Space,Str "vegetation"]],Div ("",[],[]) [Plain [Str "Dragging",Space,Str "its",Space,Str "slimy",Space,Str "belly",Space,Str "on",Space,Str "the",Space,Str "bank"]],Div ("",[],[]) [Plain [Str "While",Space,Str "I",Space,Str "was",Space,Str "fishing",Space,Str "in",Space,Str "the",Space,Str "dull",Space,Str "canal"]],Div ("",[],[]) [Plain [Str "On",Space,Str "a",Space,Str "winter",Space,Str "evening",Space,Str "round",Space,Str "behind",Space,Str "the",Space,Str "gashouse",Span ("",["lnum"],[]) [Str "190"]]],Div ("",[],[]) [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",[],[]) [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 ("",[],[]) [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 ("",[],[]) [Plain [Str "And",Space,Str "bones",Space,Str "cast",Space,Str "in",Space,Str "a",Space,Str "little",Space,Str "low",Space,Str "dry",Space,Str "garret,"]],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."]],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."]]],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 ".\""]]]]]],Div ("",[],[]) [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",[],[]) [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 ("",[],[]) [Plain [Str "And",Space,Str "on",Space,Str "her",Space,Str "daughter",Span ("",["lnum"],[]) [Str "200"]]],Div ("",[],[]) [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")]) [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 ("",[],[]) [Plain [Str "Twit",Space,Str "twit",Space,Str "twit"]],Div ("",[],[]) [Plain [Str "Jug",Space,Str "jug",Space,Str "jug",Space,Str "jug",Space,Str "jug",Space,Str "jug"]],Div ("",[],[]) [Plain [Str "So",Space,Str "rudely",Space,Str "forc'd."]],Div ("",[],[]) [Plain [Str "Tereu"]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "Unreal",Space,Str "City"]],Div ("",[],[]) [Plain [Str "Under",Space,Str "the",Space,Str "brown",Space,Str "fog",Space,Str "of",Space,Str "a",Space,Str "winter",Space,Str "noon"]],Div ("",[],[]) [Plain [Str "Mr.",Space,Str "Eugenides,",Space,Str "the",Space,Str "Smyrna",Space,Str "merchant"]],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."]]],Div ("",[],[]) [Plain [Str "C.i.f.",Space,Str "London:",Space,Str "documents",Space,Str "at",Space,Str "sight,"]],Div ("",[],[]) [Plain [Str "Asked",Space,Str "me",Space,Str "in",Space,Str "demotic",Space,Str "French"]],Div ("",[],[]) [Plain [Str "To",Space,Str "luncheon",Space,Str "at",Space,Str "the",Space,Str "Cannon",Space,Str "Street",Space,Str "Hotel"]],Div ("",[],[]) [Plain [Str "Followed",Space,Str "by",Space,Str "a",Space,Str "weekend",Space,Str "at",Space,Str "the",Space,Str "Metropole."]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "At",Space,Str "the",Space,Str "violet",Space,Str "hour,",Space,Str "when",Space,Str "the",Space,Str "eyes",Space,Str "and",Space,Str "back"]],Div ("",[],[]) [Plain [Str "Turn",Space,Str "upward",Space,Str "from",Space,Str "the",Space,Str "desk,",Space,Str "when",Space,Str "the",Space,Str "human",Space,Str "engine",Space,Str "waits"]],Div ("",[],[]) [Plain [Str "Like",Space,Str "a",Space,Str "taxi",Space,Str "throbbing",Space,Str "waiting,"]],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]]]],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"]],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"]]],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."]]],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"]],Div ("",[],[]) [Plain [Str "Her",Space,Str "stove,",Space,Str "and",Space,Str "lays",Space,Str "out",Space,Str "food",Space,Str "in",Space,Str "tins."]],Div ("",[],[]) [Plain [Str "Out",Space,Str "of",Space,Str "the",Space,Str "window",Space,Str "perilously",Space,Str "spread"]],Div ("",[],[]) [Plain [Str "Her",Space,Str "drying",Space,Str "combinations",Space,Str "touched",Space,Str "by",Space,Str "the",Space,Str "sun's",Space,Str "last",Space,Str "rays,"]],Div ("",[],[]) [Plain [Str "On",Space,Str "the",Space,Str "divan",Space,Str "are",Space,Str "piled",Space,Str "(at",Space,Str "night",Space,Str "her",Space,Str "bed)"]],Div ("",[],[]) [Plain [Str "Stockings,",Space,Str "slippers,",Space,Str "camisoles,",Space,Str "and",Space,Str "stays."]],Div ("",[],[]) [Plain [Str "I",Space,Str "Tiresias,",Space,Str "old",Space,Str "man",Space,Str "with",Space,Str "wrinkled",Space,Str "dugs"]],Div ("",[],[]) [Plain [Str "Perceived",Space,Str "the",Space,Str "scene,",Space,Str "and",Space,Str "foretold",Space,Str "the",Space,Str "rest",Space,Str "-"]],Div ("",[],[]) [Plain [Str "I",Space,Str "too",Space,Str "awaited",Space,Str "the",Space,Str "expected",Space,Str "guest.",Span ("",["lnum"],[]) [Str "230"]]],Div ("",[],[]) [Plain [Str "He,",Space,Str "the",Space,Str "young",Space,Str "man",Space,Str "carbuncular,",Space,Str "arrives,"]],Div ("",[],[]) [Plain [Str "A",Space,Str "small",Space,Str "house",Space,Str "agent's",Space,Str "clerk,",Space,Str "with",Space,Str "one",Space,Str "bold",Space,Str "stare,"]],Div ("",[],[]) [Plain [Str "One",Space,Str "of",Space,Str "the",Space,Str "low",Space,Str "on",Space,Str "whom",Space,Str "assurance",Space,Str "sits"]],Div ("",[],[]) [Plain [Str "As",Space,Str "a",Space,Str "silk",Space,Str "hat",Space,Str "on",Space,Str "a",Space,Str "Bradford",Space,Str "millionaire."]],Div ("",[],[]) [Plain [Str "The",Space,Str "time",Space,Str "is",Space,Str "now",Space,Str "propitious,",Space,Str "as",Space,Str "he",Space,Str "guesses,"]],Div ("",[],[]) [Plain [Str "The",Space,Str "meal",Space,Str "is",Space,Str "ended,",Space,Str "she",Space,Str "is",Space,Str "bored",Space,Str "and",Space,Str "tired,"]],Div ("",[],[]) [Plain [Str "Endeavours",Space,Str "to",Space,Str "engage",Space,Str "her",Space,Str "in",Space,Str "caresses"]],Div ("",[],[]) [Plain [Str "Which",Space,Str "still",Space,Str "are",Space,Str "unreproved,",Space,Str "if",Space,Str "undesired."]],Div ("",[],[]) [Plain [Str "Flushed",Space,Str "and",Space,Str "decided,",Space,Str "he",Space,Str "assaults",Space,Str "at",Space,Str "once;"]],Div ("",[],[]) [Plain [Str "Exploring",Space,Str "hands",Space,Str "encounter",Space,Str "no",Space,Str "defence;",Span ("",["lnum"],[]) [Str "240"]]],Div ("",[],[]) [Plain [Str "His",Space,Str "vanity",Space,Str "requires",Space,Str "no",Space,Str "response,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "makes",Space,Str "a",Space,Str "welcome",Space,Str "of",Space,Str "indifference."]],Div ("",[],[]) [Plain [Str "(And",Space,Str "I",Space,Str "Tiresias",Space,Str "have",Space,Str "foresuffered",Space,Str "all"]],Div ("",[],[]) [Plain [Str "Enacted",Space,Str "on",Space,Str "this",Space,Str "same",Space,Str "divan",Space,Str "or",Space,Str "bed;"]],Div ("",[],[]) [Plain [Str "I",Space,Str "who",Space,Str "have",Space,Str "sat",Space,Str "by",Space,Str "Thebes",Space,Str "below",Space,Str "the",Space,Str "wall"]],Div ("",[],[]) [Plain [Str "And",Space,Str "walked",Space,Str "among",Space,Str "the",Space,Str "lowest",Space,Str "of",Space,Str "the",Space,Str "dead.)"]],Div ("",[],[]) [Plain [Str "Bestows",Space,Str "one",Space,Str "final",Space,Str "patronising",Space,Str "kiss,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "gropes",Space,Str "his",Space,Str "way,",Space,Str "finding",Space,Str "the",Space,Str "stairs",Space,Str "unlit",Space,Str ".",Space,Str ".",Space,Str "."]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "She",Space,Str "turns",Space,Str "and",Space,Str "looks",Space,Str "a",Space,Str "moment",Space,Str "in",Space,Str "the",Space,Str "glass,"]],Div ("",[],[]) [Plain [Str "Hardly",Space,Str "aware",Space,Str "of",Space,Str "her",Space,Str "departed",Space,Str "lover;",Span ("",["lnum"],[]) [Str "250"]]],Div ("",[],[]) [Plain [Str "Her",Space,Str "brain",Space,Str "allows",Space,Str "one",Space,Str "half-formed",Space,Str "thought",Space,Str "to",Space,Str "pass:"]],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.\""]],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."]]],Div ("",[],[]) [Plain [Str "Paces",Space,Str "about",Space,Str "her",Space,Str "room",Space,Str "again,",Space,Str "alone,"]],Div ("",[],[]) [Plain [Str "She",Space,Str "smoothes",Space,Str "her",Space,Str "hair",Space,Str "with",Space,Str "automatic",Space,Str "hand,"]],Div ("",[],[]) [Plain [Str "And",Space,Str "puts",Space,Str "a",Space,Str "record",Space,Str "on",Space,Str "the",Space,Str "gramophone."]]],Div ("",["linegroup"],[]) [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."]]],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."]],Div ("",[],[]) [Plain [Str "O",Space,Str "City",Space,Str "city,",Space,Str "I",Space,Str "can",Space,Str "sometimes",Space,Str "hear"]],Div ("",[],[]) [Plain [Str "Beside",Space,Str "a",Space,Str "public",Space,Str "bar",Space,Str "in",Space,Str "Lower",Space,Str "Thames",Space,Str "Street,",Span ("",["lnum"],[]) [Str "260"]]],Div ("",[],[]) [Plain [Str "The",Space,Str "pleasant",Space,Str "whining",Space,Str "of",Space,Str "a",Space,Str "mandoline"]],Div ("",[],[]) [Plain [Str "And",Space,Str "a",Space,Str "clatter",Space,Str "and",Space,Str "a",Space,Str "chatter",Space,Str "from",Space,Str "within"]],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"]],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.)."]]],Div ("",[],[]) [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 ("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."]]],Div ("",[],[]) [Plain [Str "Oil",Space,Str "and",Space,Str "tar"]],Div ("",[],[]) [Plain [Str "The",Space,Str "barges",Space,Str "drift"]],Div ("",[],[]) [Plain [Str "With",Space,Str "the",Space,Str "turning",Space,Str "tide"]],Div ("",[],[]) [Plain [Str "Red",Space,Str "sails",Span ("",["lnum"],[]) [Str "270"]]],Div ("",[],[]) [Plain [Str "Wide"]],Div ("",[],[]) [Plain [Str "To",Space,Str "leeward,",Space,Str "swing",Space,Str "on",Space,Str "the",Space,Str "heavy",Space,Str "spar."]],Div ("",[],[]) [Plain [Str "The",Space,Str "barges",Space,Str "wash"]],Div ("",[],[]) [Plain [Str "Drifting",Space,Str "logs"]],Div ("",[],[]) [Plain [Str "Down",Space,Str "Greenwich",Space,Str "reach"]],Div ("",[],[]) [Plain [Str "Past",Space,Str "the",Space,Str "Isle",Space,Str "of",Space,Str "Dogs."]],Div ("",["indent"],[]) [Plain [Str "Weialala",Space,Str "leia"]],Div ("",["indent"],[]) [Plain [Str "Wallala",Space,Str "leialala"]]],Div ("",["linegroup","indent"],[]) [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.\""]]]]]],Div ("",[],[]) [Plain [Str "Beating",Space,Str "oars",Span ("",["lnum"],[]) [Str "280"]]],Div ("",[],[]) [Plain [Str "The",Space,Str "stern",Space,Str "was",Space,Str "formed"]],Div ("",[],[]) [Plain [Str "A",Space,Str "gilded",Space,Str "shell"]],Div ("",[],[]) [Plain [Str "Red",Space,Str "and",Space,Str "gold"]],Div ("",[],[]) [Plain [Str "The",Space,Str "brisk",Space,Str "swell"]],Div ("",[],[]) [Plain [Str "Rippled",Space,Str "both",Space,Str "shores"]],Div ("",[],[]) [Plain [Str "Southwest",Space,Str "wind"]],Div ("",[],[]) [Plain [Str "Carried",Space,Str "down",Space,Str "stream"]],Div ("",[],[]) [Plain [Str "The",Space,Str "peal",Space,Str "of",Space,Str "bells"]],Div ("",[],[]) [Plain [Str "White",Space,Str "towers"]],Div ("",["indent"],[]) [Plain [Str "Weialala",Space,Str "leia",Span ("",["lnum"],[]) [Str "290"]]],Div ("",["indent"],[]) [Plain [Str "Wallala",Space,Str "leialala"]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "\"Trams",Space,Str "and",Space,Str "dusty",Space,Str "trees."]],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.\""]]]],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"]],Div ("",[],[]) [Plain [Str "Supine",Space,Str "on",Space,Str "the",Space,Str "floor",Space,Str "of",Space,Str "a",Space,Str "narrow",Space,Str "canoe.\""]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "\"My",Space,Str "feet",Space,Str "are",Space,Str "at",Space,Str "Moorgate,",Space,Str "and",Space,Str "my",Space,Str "heart"]],Div ("",[],[]) [Plain [Str "Under",Space,Str "my",Space,Str "feet.",Space,Str "After",Space,Str "the",Space,Str "event"]],Div ("",[],[]) [Plain [Str "He",Space,Str "wept.",Space,Str "He",Space,Str "promised",Space,Str "'a",Space,Str "new",Space,Str "start'."]],Div ("",[],[]) [Plain [Str "I",Space,Str "made",Space,Str "no",Space,Str "comment.",Space,Str "What",Space,Str "should",Space,Str "I",Space,Str "resent?\""]],Div ("",[],[]) [Plain [Str "\"On",Space,Str "Margate",Space,Str "Sands.",Span ("",["lnum"],[]) [Str "300"]]],Div ("",[],[]) [Plain [Str "I",Space,Str "can",Space,Str "connect"]],Div ("",[],[]) [Plain [Str "Nothing",Space,Str "with",Space,Str "nothing."]],Div ("",[],[]) [Plain [Str "The",Space,Str "broken",Space,Str "fingernails",Space,Str "of",Space,Str "dirty",Space,Str "hands."]],Div ("",[],[]) [Plain [Str "My",Space,Str "people",Space,Str "humble",Space,Str "people",Space,Str "who",Space,Str "expect"]],Div ("",[],[]) [Plain [Str "Nothing.\""]],Div ("",["indent"],[]) [Plain [Str "la",Space,Str "la"]]],Div ("",["linegroup"],[]) [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.\""]]],Div ("",["linegroup"],[]) [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."]]],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."]]],Div ("",[],[]) [Plain [Str "O",Space,Str "Lord",Space,Str "Thou",Space,Str "pluckest",Span ("",["lnum"],[]) [Str "310"]]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "burning"]]],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 2 ("",[],[]) [Str "IV.",Space,Str "DEATH",Space,Str "BY",Space,Str "WATER"],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "Phlebas",Space,Str "the",Space,Str "Phoenician,",Space,Str "a",Space,Str "fortnight",Space,Str "dead,"]],Div ("",[],[]) [Plain [Str "Forgot",Space,Str "the",Space,Str "cry",Space,Str "of",Space,Str "gulls,",Space,Str "and",Space,Str "the",Space,Str "deep",Space,Str "sea",Space,Str "swell"]],Div ("",[],[]) [Plain [Str "And",Space,Str "the",Space,Str "profit",Space,Str "and",Space,Str "loss."]]],Div ("",["linegroup"],[]) [Div ("",["indent2"],[]) [Plain [Str "A",Space,Str "current",Space,Str "under",Space,Str "sea"]],Div ("",[],[]) [Plain [Str "Picked",Space,Str "his",Space,Str "bones",Space,Str "in",Space,Str "whispers.",Space,Str "As",Space,Str "he",Space,Str "rose",Space,Str "and",Space,Str "fell"]],Div ("",[],[]) [Plain [Str "He",Space,Str "passed",Space,Str "the",Space,Str "stages",Space,Str "of",Space,Str "his",Space,Str "age",Space,Str "and",Space,Str "youth"]],Div ("",[],[]) [Plain [Str "Entering",Space,Str "the",Space,Str "whirlpool."]]],Div ("",["linegroup"],[]) [Div ("",["indent2"],[]) [Plain [Str "Gentile",Space,Str "or",Space,Str "Jew"]],Div ("",[],[]) [Plain [Str "O",Space,Str "you",Space,Str "who",Space,Str "turn",Space,Str "the",Space,Str "wheel",Space,Str "and",Space,Str "look",Space,Str "to",Space,Str "windward,",Span ("",["lnum"],[]) [Str "320"]]],Div ("",[],[]) [Plain [Str "Consider",Space,Str "Phlebas,",Space,Str "who",Space,Str "was",Space,Str "once",Space,Str "handsome",Space,Str "and",Space,Str "tall",Space,Str "as",Space,Str "you."]]],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 2 ("",[],[]) [Str "V.",Space,Str "WHAT",Space,Str "THE",Space,Str "THUNDER",Space,Str "SAID"],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "After",Space,Str "the",Space,Str "torchlight",Space,Str "red",Space,Str "on",Space,Str "sweaty",Space,Str "faces"]],Div ("",[],[]) [Plain [Str "After",Space,Str "the",Space,Str "frosty",Space,Str "silence",Space,Str "in",Space,Str "the",Space,Str "gardens"]],Div ("",[],[]) [Plain [Str "After",Space,Str "the",Space,Str "agony",Space,Str "in",Space,Str "stony",Space,Str "places"]],Div ("",[],[]) [Plain [Str "The",Space,Str "shouting",Space,Str "and",Space,Str "the",Space,Str "crying"]],Div ("",[],[]) [Plain [Str "Prison",Space,Str "and",Space,Str "palace",Space,Str "and",Space,Str "reverberation"]],Div ("",[],[]) [Plain [Str "Of",Space,Str "thunder",Space,Str "of",Space,Str "spring",Space,Str "over",Space,Str "distant",Space,Str "mountains"]],Div ("",[],[]) [Plain [Str "He",Space,Str "who",Space,Str "was",Space,Str "living",Space,Str "is",Space,Str "now",Space,Str "dead"]],Div ("",[],[]) [Plain [Str "We",Space,Str "who",Space,Str "were",Space,Str "living",Space,Str "are",Space,Str "now",Space,Str "dying"]],Div ("",[],[]) [Plain [Str "With",Space,Str "a",Space,Str "little",Space,Str "patience",Span ("",["lnum"],[]) [Str "330"]]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "Here",Space,Str "is",Space,Str "no",Space,Str "water",Space,Str "but",Space,Str "only",Space,Str "rock"]],Div ("",[],[]) [Plain [Str "Rock",Space,Str "and",Space,Str "no",Space,Str "water",Space,Str "and",Space,Str "the",Space,Str "sandy",Space,Str "road"]],Div ("",[],[]) [Plain [Str "The",Space,Str "road",Space,Str "winding",Space,Str "above",Space,Str "among",Space,Str "the",Space,Str "mountains"]],Div ("",[],[]) [Plain [Str "Which",Space,Str "are",Space,Str "mountains",Space,Str "of",Space,Str "rock",Space,Str "without",Space,Str "water"]],Div ("",[],[]) [Plain [Str "If",Space,Str "there",Space,Str "were",Space,Str "water",Space,Str "we",Space,Str "should",Space,Str "stop",Space,Str "and",Space,Str "drink"]],Div ("",[],[]) [Plain [Str "Amongst",Space,Str "the",Space,Str "rock",Space,Str "one",Space,Str "cannot",Space,Str "stop",Space,Str "or",Space,Str "think"]],Div ("",[],[]) [Plain [Str "Sweat",Space,Str "is",Space,Str "dry",Space,Str "and",Space,Str "feet",Space,Str "are",Space,Str "in",Space,Str "the",Space,Str "sand"]],Div ("",[],[]) [Plain [Str "If",Space,Str "there",Space,Str "were",Space,Str "only",Space,Str "water",Space,Str "amongst",Space,Str "the",Space,Str "rock"]],Div ("",[],[]) [Plain [Str "Dead",Space,Str "mountain",Space,Str "mouth",Space,Str "of",Space,Str "carious",Space,Str "teeth",Space,Str "that",Space,Str "cannot",Space,Str "spit"]],Div ("",[],[]) [Plain [Str "Here",Space,Str "one",Space,Str "can",Space,Str "neither",Space,Str "stand",Space,Str "nor",Space,Str "lie",Space,Str "nor",Space,Str "sit",Span ("",["lnum"],[]) [Str "340"]]],Div ("",[],[]) [Plain [Str "There",Space,Str "is",Space,Str "not",Space,Str "even",Space,Str "silence",Space,Str "in",Space,Str "the",Space,Str "mountains"]],Div ("",[],[]) [Plain [Str "But",Space,Str "dry",Space,Str "sterile",Space,Str "thunder",Space,Str "without",Space,Str "rain"]],Div ("",[],[]) [Plain [Str "There",Space,Str "is",Space,Str "not",Space,Str "even",Space,Str "solitude",Space,Str "in",Space,Str "the",Space,Str "mountains"]],Div ("",[],[]) [Plain [Str "But",Space,Str "red",Space,Str "sullen",Space,Str "faces",Space,Str "sneer",Space,Str "and",Space,Str "snarl"]],Div ("",[],[]) [Plain [Str "From",Space,Str "doors",Space,Str "of",Space,Str "mudcracked",Space,Str "houses"]],Div ("",["linegroup"],[]) [Div ("",["indent2"],[]) [Plain [Str "If",Space,Str "there",Space,Str "were",Space,Str "water"]],Div ("",[],[]) [Plain [Str "And",Space,Str "no",Space,Str "rock"]],Div ("",[],[]) [Plain [Str "If",Space,Str "there",Space,Str "were",Space,Str "rock"]],Div ("",[],[]) [Plain [Str "And",Space,Str "also",Space,Str "water"]],Div ("",[],[]) [Plain [Str "And",Space,Str "water",Span ("",["lnum"],[]) [Str "350"]]],Div ("",[],[]) [Plain [Str "A",Space,Str "spring"]],Div ("",[],[]) [Plain [Str "A",Space,Str "pool",Space,Str "among",Space,Str "the",Space,Str "rock"]],Div ("",[],[]) [Plain [Str "If",Space,Str "there",Space,Str "were",Space,Str "the",Space,Str "sound",Space,Str "of",Space,Str "water",Space,Str "only"]],Div ("",[],[]) [Plain [Str "Not",Space,Str "the",Space,Str "cicada"]],Div ("",[],[]) [Plain [Str "And",Space,Str "dry",Space,Str "grass",Space,Str "singing"]],Div ("",[],[]) [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",[],[]) [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 ("",[],[]) [Plain [Str "Drip",Space,Str "drop",Space,Str "drip",Space,Str "drop",Space,Str "drop",Space,Str "drop",Space,Str "drop"]],Div ("",[],[]) [Plain [Str "But",Space,Str "there",Space,Str "is",Space,Str "no",Space,Str "water"]]]],Div ("",["linegroup"],[]) [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."]]],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"]],Div ("",[],[]) [Plain [Str "But",Space,Str "when",Space,Str "I",Space,Str "look",Space,Str "ahead",Space,Str "up",Space,Str "the",Space,Str "white",Space,Str "road"]],Div ("",[],[]) [Plain [Str "There",Space,Str "is",Space,Str "always",Space,Str "another",Space,Str "one",Space,Str "walking",Space,Str "beside",Space,Str "you"]],Div ("",[],[]) [Plain [Str "Gliding",Space,Str "wrapt",Space,Str "in",Space,Str "a",Space,Str "brown",Space,Str "mantle,",Space,Str "hooded"]],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"]],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.\""]]]],Div ("",["linegroup"],[]) [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"]],Div ("",[],[]) [Plain [Str "Murmur",Space,Str "of",Space,Str "maternal",Space,Str "lamentation"]],Div ("",[],[]) [Plain [Str "Who",Space,Str "are",Space,Str "those",Space,Str "hooded",Space,Str "hordes",Space,Str "swarming"]],Div ("",[],[]) [Plain [Str "Over",Space,Str "endless",Space,Str "plains,",Space,Str "stumbling",Space,Str "in",Space,Str "cracked",Space,Str "earth",Span ("",["lnum"],[]) [Str "370"]]],Div ("",[],[]) [Plain [Str "Ringed",Space,Str "by",Space,Str "the",Space,Str "flat",Space,Str "horizon",Space,Str "only"]],Div ("",[],[]) [Plain [Str "What",Space,Str "is",Space,Str "the",Space,Str "city",Space,Str "over",Space,Str "the",Space,Str "mountains"]],Div ("",[],[]) [Plain [Str "Cracks",Space,Str "and",Space,Str "reforms",Space,Str "and",Space,Str "bursts",Space,Str "in",Space,Str "the",Space,Str "violet",Space,Str "air"]],Div ("",[],[]) [Plain [Str "Falling",Space,Str "towers"]],Div ("",[],[]) [Plain [Str "Jerusalem",Space,Str "Athens",Space,Str "Alexandria"]],Div ("",[],[]) [Plain [Str "Vienna",Space,Str "London"]],Div ("",[],[]) [Plain [Str "Unreal"]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "A",Space,Str "woman",Space,Str "drew",Space,Str "her",Space,Str "long",Space,Str "black",Space,Str "hair",Space,Str "out",Space,Str "tight"]],Div ("",[],[]) [Plain [Str "And",Space,Str "fiddled",Space,Str "whisper",Space,Str "music",Space,Str "on",Space,Str "those",Space,Str "strings"]],Div ("",[],[]) [Plain [Str "And",Space,Str "bats",Space,Str "with",Space,Str "baby",Space,Str "faces",Space,Str "in",Space,Str "the",Space,Str "violet",Space,Str "light",Span ("",["lnum"],[]) [Str "380"]]],Div ("",[],[]) [Plain [Str "Whistled,",Space,Str "and",Space,Str "beat",Space,Str "their",Space,Str "wings"]],Div ("",[],[]) [Plain [Str "And",Space,Str "crawled",Space,Str "head",Space,Str "downward",Space,Str "down",Space,Str "a",Space,Str "blackened",Space,Str "wall"]],Div ("",[],[]) [Plain [Str "And",Space,Str "upside",Space,Str "down",Space,Str "in",Space,Str "air",Space,Str "were",Space,Str "towers"]],Div ("",[],[]) [Plain [Str "Tolling",Space,Str "reminiscent",Space,Str "bells,",Space,Str "that",Space,Str "kept",Space,Str "the",Space,Str "hours"]],Div ("",[],[]) [Plain [Str "And",Space,Str "voices",Space,Str "singing",Space,Str "out",Space,Str "of",Space,Str "empty",Space,Str "cisterns",Space,Str "and",Space,Str "exhausted",Space,Str "wells."]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "In",Space,Str "this",Space,Str "decayed",Space,Str "hole",Space,Str "among",Space,Str "the",Space,Str "mountains"]],Div ("",[],[]) [Plain [Str "In",Space,Str "the",Space,Str "faint",Space,Str "moonlight,",Space,Str "the",Space,Str "grass",Space,Str "is",Space,Str "singing"]],Div ("",[],[]) [Plain [Str "Over",Space,Str "the",Space,Str "tumbled",Space,Str "graves,",Space,Str "about",Space,Str "the",Space,Str "chapel"]],Div ("",[],[]) [Plain [Str "There",Space,Str "is",Space,Str "the",Space,Str "empty",Space,Str "chapel,",Space,Str "only",Space,Str "the",Space,Str "wind's",Space,Str "home."]],Div ("",[],[]) [Plain [Str "It",Space,Str "has",Space,Str "no",Space,Str "windows,",Space,Str "and",Space,Str "the",Space,Str "door",Space,Str "swings,",Span ("",["lnum"],[]) [Str "390"]]],Div ("",[],[]) [Plain [Str "Dry",Space,Str "bones",Space,Str "can",Space,Str "harm",Space,Str "no",Space,Str "one."]],Div ("",[],[]) [Plain [Str "Only",Space,Str "a",Space,Str "cock",Space,Str "stood",Space,Str "on",Space,Str "the",Space,Str "rooftree"]],Div ("",[],[]) [Plain [Str "Co",Space,Str "co",Space,Str "rico",Space,Str "co",Space,Str "co",Space,Str "rico"]],Div ("",[],[]) [Plain [Str "In",Space,Str "a",Space,Str "flash",Space,Str "of",Space,Str "lightning.",Space,Str "Then",Space,Str "a",Space,Str "damp",Space,Str "gust"]],Div ("",[],[]) [Plain [Str "Bringing",Space,Str "rain"]]],Div ("",["linegroup"],[]) [Div ("",[],[]) [Plain [Str "Ganga",Space,Str "was",Space,Str "sunken,",Space,Str "and",Space,Str "the",Space,Str "limp",Space,Str "leaves"]],Div ("",[],[]) [Plain [Str "Waited",Space,Str "for",Space,Str "rain,",Space,Str "while",Space,Str "the",Space,Str "black",Space,Str "clouds"]],Div ("",[],[]) [Plain [Str "Gathered",Space,Str "far",Space,Str "distant,",Space,Str "over",Space,Str "Himavant."]],Div ("",[],[]) [Plain [Str "The",Space,Str "jungle",Space,Str "crouched,",Space,Str "humped",Space,Str "in",Space,Str "silence."]],Div ("",[],[]) [Plain [Str "Then",Space,Str "spoke",Space,Str "the",Space,Str "thunder",Span ("",["lnum"],[]) [Str "400"]]],Div ("",[],[]) [Plain [Str "DA"]],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."]]],Div ("",[],[]) [Plain [Str "My",Space,Str "friend,",Space,Str "blood",Space,Str "shaking",Space,Str "my",Space,Str "heart"]],Div ("",[],[]) [Plain [Str "The",Space,Str "awful",Space,Str "daring",Space,Str "of",Space,Str "a",Space,Str "moment's",Space,Str "surrender"]],Div ("",[],[]) [Plain [Str "Which",Space,Str "an",Space,Str "age",Space,Str "of",Space,Str "prudence",Space,Str "can",Space,Str "never",Space,Str "retract"]],Div ("",[],[]) [Plain [Str "By",Space,Str "this,",Space,Str "and",Space,Str "this",Space,Str "only,",Space,Str "we",Space,Str "have",Space,Str "existed"]],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"]],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.\""]]]],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"]],Div ("",[],[]) [Plain [Str "In",Space,Str "our",Space,Str "empty",Space,Str "rooms",Span ("",["lnum"],[]) [Str "410"]]],Div ("",[],[]) [Plain [Str "DA"]],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.\""]]]],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"]],Div ("",[],[]) [Plain [Str "We",Space,Str "think",Space,Str "of",Space,Str "the",Space,Str "key,",Space,Str "each",Space,Str "in",Space,Str "his",Space,Str "prison"]],Div ("",[],[]) [Plain [Str "Thinking",Space,Str "of",Space,Str "the",Space,Str "key,",Space,Str "each",Space,Str "confirms",Space,Str "a",Space,Str "prison"]],Div ("",[],[]) [Plain [Str "Only",Space,Str "at",Space,Str "nightfall,",Space,Str "aetherial",Space,Str "rumours"]],Div ("",[],[]) [Plain [Str "Revive",Space,Str "for",Space,Str "a",Space,Str "moment",Space,Str "a",Space,Str "broken",Space,Str "Coriolanus"]],Div ("",[],[]) [Plain [Str "DA"]],Div ("",[],[]) [Plain [Span ("",[],[("lang","sa")]) [Str "Damyata"],Str ":",Space,Str "The",Space,Str "boat",Space,Str "responded"]],Div ("",[],[]) [Plain [Str "Gaily,",Space,Str "to",Space,Str "the",Space,Str "hand",Space,Str "expert",Space,Str "with",Space,Str "sail",Space,Str "and",Space,Str "oar",Span ("",["lnum"],[]) [Str "420"]]],Div ("",[],[]) [Plain [Str "The",Space,Str "sea",Space,Str "was",Space,Str "calm,",Space,Str "your",Space,Str "heart",Space,Str "would",Space,Str "have",Space,Str "responded"]],Div ("",[],[]) [Plain [Str "Gaily,",Space,Str "when",Space,Str "invited,",Space,Str "beating",Space,Str "obedient"]],Div ("",[],[]) [Plain [Str "To",Space,Str "controlling",Space,Str "hands"]]],Div ("",["linegroup"],[]) [Div ("",["indent"],[]) [Plain [Str "I",Space,Str "sat",Space,Str "upon",Space,Str "the",Space,Str "shore"]],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."]]],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?"]],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"]],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.\""]]]],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."]]],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."]]],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"]],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."]]],Div ("",[],[("lang","sa")]) [Plain [Str "Datta.",Space,Str "Dayadhvam.",Space,Str "Damyata."]],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."]]]],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 2 ("",[],[]) [Str "NOTES",Space,Str "ON",Space,Str "\"THE",Space,Str "WASTE",Space,Str "LAND\""],Para [Str "Not",Space,Str "only",Space,Str "the",Space,Str "title,",Space,Str "but",Space,Str "the",Space,Str "plan",Space,Str "and",Space,Str "a",Space,Str "good",Space,Str "deal",Space,Str "of",Space,Str "the",Space,Str "incidental",Space,Str "symbolism",Space,Str "of",Space,Str "the",Space,Str "poem",Space,Str "were",Space,Str "suggested",Space,Str "by",Space,Str "Miss",Space,Str "Jessie",Space,Str "L.",Space,Str "Weston's",Space,Str "book",Space,Str "on",Space,Str "the",Space,Str "Grail",Space,Str "legend:",Space,Str "From",Space,Str "Ritual",Space,Str "to",Space,Str "Romance"],Para [Str "Indeed,",Space,Str "so",Space,Str "deeply",Space,Str "am",Space,Str "I",Space,Str "indebted,",Space,Str "Miss",Space,Str "Weston's",Space,Str "book",Space,Str "will",Space,Str "elucidate",Space,Str "the",Space,Str "difficulties",Space,Str "of",Space,Str "the",Space,Str "poem",Space,Str "much",Space,Str "better",Space,Str "than",Space,Str "my",Space,Str "notes",Space,Str "can",Space,Str "do;",Space,Str "and",Space,Str "I",Space,Str "recommend",Space,Str "it",Space,Str "(apart",Space,Str "from",Space,Str "the",Space,Str "great",Space,Str "interest",Space,Str "of",Space,Str "the",Space,Str "book",Space,Str "itself)",Space,Str "to",Space,Str "any",Space,Str "who",Space,Str "think",Space,Str "such",Space,Str "elucidation",Space,Str "of",Space,Str "the",Space,Str "poem",Space,Str "worth",Space,Str "the",Space,Str "trouble.",Space,Str "To",Space,Str "another",Space,Str "work",Space,Str "of",Space,Str "anthropology",Space,Str "I",Space,Str "am",Space,Str "indebted",Space,Str "in",Space,Str "general,",Space,Str "one",Space,Str "which",Space,Str "has",Space,Str "influenced",Space,Str "our",Space,Str "generation",Space,Str "profoundly;",Space,Str "I",Space,Str "mean",Space,Str "The",Space,Str "Golden",Space,Str "Bough;",Space,Str "I",Space,Str "have",Space,Str "used",Space,Str "especially",Space,Str "the",Space,Str "two",Space,Str "volumes",Space,Str "Adonis,",Space,Str "Attis,",Space,Str "Osiris.",Space,Str "Anyone",Space,Str "who",Space,Str "is",Space,Str "acquainted",Space,Str "with",Space,Str "these",Space,Str "works",Space,Str "will",Space,Str "immediately",Space,Str "recognise",Space,Str "in",Space,Str "the",Space,Str "poem",Space,Str "certain",Space,Str "references",Space,Str "to",Space,Str "vegetation",Space,Str "ceremonies."],RawBlock (Format "html") "
",Header 3 ("",[],[]) [Str "I.",Space,Str "THE",Space,Str "BURIAL",Space,Str "OF",Space,Str "THE",Space,Str "DEAD"],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 3 ("",[],[]) [Str "II.",Space,Str "A",Space,Str "GAME",Space,Str "OF",Space,Str "CHESS"],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 3 ("",[],[]) [Str "III.",Space,Str "THE",Space,Str "FIRE",Space,Str "SERMON"],RawBlock (Format "html") "
",RawBlock (Format "html") "
",Header 3 ("",[],[]) [Str "V.",Space,Str "WHAT",Space,Str "THE",Space,Str "THUNDER",Space,Str "SAID"],Para [Str "In",Space,Str "the",Space,Str "first",Space,Str "part",Space,Str "of",Space,Str "Part",Space,Str "V",Space,Str "three",Space,Str "themes",Space,Str "are",Space,Str "employed:",Space,Str "the",Space,Str "journey",Space,Str "to",Space,Str "Emmaus,",Space,Str "the",Space,Str "approach",Space,Str "to",Space,Str "the",Space,Str "Chapel",Space,Str "Perilous",Space,Str "(see",Space,Str "Miss",Space,Str "Weston's",Space,Str "book)",Space,Str "and",Space,Str "the",Space,Str "present",Space,Str "decay",Space,Str "of",Space,Str "eastern",Space,Str "Europe."],RawBlock (Format "html") "
",RawBlock (Format "html") "
",RawBlock (Format "html") "
"]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]]] diff --git a/tests/haddock-reader.native b/tests/haddock-reader.native index b62189046..0deb8b1ca 100644 --- a/tests/haddock-reader.native +++ b/tests/haddock-reader.native @@ -1,5 +1,5 @@ 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 "*",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."] @@ -26,6 +26,6 @@ Pandoc (Meta {unMeta = fromList []}) [[Para [Str "The",Space,Str "description",Space,Str "of",Space,Code ("",[],[]) "foo",Str "."]]]) ,([Code ("",[],[]) "bar"], [[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 [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 [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 "Click",Space,Str "Here!"] ("http://example.com","http://example.com")]] diff --git a/tests/html-reader.native b/tests/html-reader.native index 13ee9d516..09a51a7a3 100644 --- a/tests/html-reader.native +++ b/tests/html-reader.native @@ -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."] ,HorizontalRule ,Header 1 ("",[],[]) [Str "Headers"] -,Header 2 ("",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link [Str "embedded",Space,Str "link"] ("/url","")] +,Header 2 ("",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link ("",[],[]) [Str "embedded",Space,Str "link"] ("/url","")] ,Header 3 ("",[],[]) [Str "Level",Space,Str "3",Space,Str "with",Space,Emph [Str "emphasis"]] ,Header 4 ("",[],[]) [Str "Level",Space,Str "4"] ,Header 5 ("",[],[]) [Str "Level",Space,Str "5"] @@ -187,7 +187,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,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 "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 [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."]]] @@ -200,7 +200,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 "'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 "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 "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 "."] @@ -256,41 +256,41 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl ,HorizontalRule ,Header 1 ("",[],[]) [Str "Links"] ,Header 2 ("",[],[]) [Str "Explicit"] -,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 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 with \"quotes\" in it")] -,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","title with single quotes")] +,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 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 with \"quotes\" in it")] +,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 [Link [Str "Empty"] ("",""),Str "."] +,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."] ,Header 2 ("",[],[]) [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 "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 [Str "Indented",Space,Link [Str "once"] ("/url",""),Str "."] -,Para [Str "Indented",Space,Link [Str "twice"] ("/url",""),Str "."] -,Para [Str "Indented",Space,Link [Str "thrice"] ("/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 [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 "twice"] ("/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."] ,CodeBlock ("",[],[]) "[not]: /url" -,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 "bar"] ("/url/","Title with \"quotes\" inside"),Str "."] +,Para [Str "Foo",Space,Link ("",[],[]) [Str "biz"] ("/url/","Title with \"quote\" inside"),Str "."] ,Header 2 ("",[],[]) [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,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",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?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 "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 "."] ,Header 2 ("",[],[]) [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 [[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."]]] ,Para [Str "An",Space,Str "e-mail",Space,Str "address:",Space,Str "nobody",Space,Str "[at]",Space,Str "nowhere.net"] ,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 ("",[],[]) ""] ,CodeBlock ("",[],[]) "or here: " ,HorizontalRule @@ -300,9 +300,9 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [Str "movie"] ("movie.jpg",""),Space,Str "icon."] ,HorizontalRule ,Header 1 ("",[],[]) [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 [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 [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 "(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)."] ,CodeBlock ("",[],[]) " { }" ,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."] diff --git a/tests/latex-reader.native b/tests/latex-reader.native index 8f51e409f..0bb24714e 100644 --- a/tests/latex-reader.native +++ b/tests/latex-reader.native @@ -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."] ,HorizontalRule ,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"]] ,Para [Str "Level",Space,Str "4"] ,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"] ,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 "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 [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."]]] @@ -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 "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 [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 "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."] @@ -320,42 +320,42 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,HorizontalRule ,Header 1 ("links",[],[]) [Str "Links"] ,Header 2 ("explicit",[],[]) [Str "Explicit"] -,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/","")] -,Para [Link [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","")] -,Para [Link [Str "with_underscore"] ("/url/with_underscore","")] -,Para [Link [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")] -,Para [Link [Str "Empty"] ("",""),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/","")] +,Para [Link ("",[],[]) [Str "URL",Space,Str "and",Space,Str "title"] ("/url/","")] +,Para [Link ("",[],[]) [Str "with_underscore"] ("/url/with_underscore","")] +,Para [Link ("",[],[]) [Str "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")] +,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."] ,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 "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 [Str "Indented",Space,Link [Str "once"] ("/url",""),Str "."] -,Para [Str "Indented",Space,Link [Str "twice"] ("/url",""),Str "."] -,Para [Str "Indented",Space,Link [Str "thrice"] ("/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 [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 "twice"] ("/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."] ,CodeBlock ("",[],[]) "[not]: /url" -,Para [Str "Foo",Space,Link [Str "bar"] ("/url/",""),Str "."] -,Para [Str "Foo",Space,Link [Str "biz"] ("/url/",""),Str "."] +,Para [Str "Foo",Space,Link ("",[],[]) [Str "bar"] ("/url/",""),Str "."] +,Para [Str "Foo",Space,Link ("",[],[]) [Str "biz"] ("/url/",""),Str "."] ,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,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",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?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 "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 "."] ,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 [[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 "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 - [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 ("",[],[]) ""] ,CodeBlock ("",[],[]) "or here: " ,HorizontalRule @@ -365,7 +365,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [Str "image"] ("movie.jpg",""),Space,Str "icon."] ,HorizontalRule ,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 ("",[],[]) " { }",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 ("",[],[]) " { }",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 [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) diff --git a/tests/markdown-reader-more.native b/tests/markdown-reader-more.native index b046d44d5..5ce8e98b6 100644 --- a/tests/markdown-reader-more.native +++ b/tests/markdown-reader-more.native @@ -1,14 +1,14 @@ [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"] -,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"] ,Plain [RawInline (Format "tex") "\\placeformula "] ,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]" ,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 "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 "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 "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"] ,HorizontalRule ,HorizontalRule @@ -42,9 +42,9 @@ ,Para [Str "`hi"] ,Para [Str "there`"] ,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 "foo"] ("/bar/\27979?x=\27979","title")] -,Para [Link [Str "\27979@foo.\27979.baz"] ("mailto:\27979@foo.\27979.baz","")] +,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 "\27979@foo.\27979.baz"] ("mailto:\27979@foo.\27979.baz","")] ,Header 2 ("numbered-examples",[],[]) [Str "Numbered",Space,Str "examples"] ,OrderedList (1,Example,TwoParens) [[Plain [Str "First",Space,Str "example."]] @@ -55,9 +55,9 @@ ,Header 2 ("macros",[],[]) [Str "Macros"] ,Para [Math InlineMath "{\\langle x,y \\rangle}"] ,Header 2 ("case-insensitive-references",[],[]) [Str "Case-insensitive",Space,Str "references"] -,Para [Link [Str "Fum"] ("/fum","")] -,Para [Link [Str "FUM"] ("/fum","")] -,Para [Link [Str "bat"] ("/bat","")] +,Para [Link ("",[],[]) [Str "Fum"] ("/fum","")] +,Para [Link ("",[],[]) [Str "FUM"] ("/fum","")] +,Para [Link ("",[],[]) [Str "bat"] ("/bat","")] ,Header 2 ("curly-smart-quotes",[],[]) [Str "Curly",Space,Str "smart",Space,Str "quotes"] ,Para [Quoted DoubleQuote [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 3 ("my-header-1",[],[]) [Str "My",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 "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 "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 "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 "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 "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"] ,BlockQuote [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"] -,Para [Link [Str "link"] ("/\252rl","\246\246!")] -,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 "foobar"] ("/\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 "me@ex\228mple.com"] ("mailto:me@ex\228mple.com","")] +,Para [Link ("",[],[]) [Str "foobar"] ("/\252rl","\246\246!")] ,Header 2 ("parentheses-in-urls",[],[]) [Str "Parentheses",Space,Str "in",Space,Str "URLs"] -,Para [Link [Str "link"] ("/hi(there)","")] -,Para [Link [Str "link"] ("/hithere)","")] -,Para [Link [Str "linky"] ("hi_(there_(nested))","")] +,Para [Link ("",[],[]) [Str "link"] ("/hi(there)","")] +,Para [Link ("",[],[]) [Str "link"] ("/hithere)","")] +,Para [Link ("",[],[]) [Str "linky"] ("hi_(there_(nested))","")] ,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"] ,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"] -,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"] ,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"] ,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."]]]] diff --git a/tests/mediawiki-reader.native b/tests/mediawiki-reader.native index d03182146..16824ced8 100644 --- a/tests/mediawiki-reader.native +++ b/tests/mediawiki-reader.native @@ -71,18 +71,18 @@ Pandoc (Meta {unMeta = fromList []}) ,Para [Str "With",Space,Str "two",Space,Str "paragraphs."]] ,Para [Str "Nother",Space,Str "paragraph."] ,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 [Str "http://pandoc.org"] ("http://pandoc.org","")] -,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 ("",[],[]) [Emph [Str "Google"],Space,Str "search",Space,Str "engine"] ("http://google.com","")] +,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 "email",Space,Str "me"] ("mailto:info@example.org","")] ,Header 2 ("internal-links",[],[]) [Str "internal",Space,Str "links"] -,Para [Link [Str "Help"] ("Help","wikilink")] -,Para [Link [Str "the",Space,Str "help",Space,Str "page"] ("Help","wikilink")] -,Para [Link [Str "Helpers"] ("Help","wikilink")] -,Para [Link [Str "Help"] ("Help","wikilink"),Str "ers"] -,Para [Link [Str "Contents"] ("Help:Contents","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 "Help"] ("Help","wikilink")] +,Para [Link ("",[],[]) [Str "the",Space,Str "help",Space,Str "page"] ("Help","wikilink")] +,Para [Link ("",[],[]) [Str "Helpers"] ("Help","wikilink")] +,Para [Link ("",[],[]) [Str "Help"] ("Help","wikilink"),Str "ers"] +,Para [Link ("",[],[]) [Str "Contents"] ("Help:Contents","wikilink")] +,Para [Link ("",[],[]) [Str "#My",Space,Str "anchor"] ("#My_anchor","wikilink")] +,Para [Link ("",[],[]) [Str "and",Space,Str "text"] ("Page#with_anchor","wikilink")] ,Header 2 ("images",[],[]) [Str "images"] ,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")] @@ -254,4 +254,4 @@ Pandoc (Meta {unMeta = fromList []}) ,Para [Str "Paragraph",Space,Str "after",Space,Str "the",Space,Str "table."] ,Header 2 ("notes",[],[]) [Str "notes"] ,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","")]]]] diff --git a/tests/odt/native/referenceToChapter.native b/tests/odt/native/referenceToChapter.native index fc6c6cf5c..544fcaaf1 100644 --- a/tests/odt/native/referenceToChapter.native +++ b/tests/odt/native/referenceToChapter.native @@ -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 "."]] \ No newline at end of file +[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 "."]] diff --git a/tests/odt/native/referenceToListItem.native b/tests/odt/native/referenceToListItem.native index d009f8d23..e64389ce6 100644 --- a/tests/odt/native/referenceToListItem.native +++ b/tests/odt/native/referenceToListItem.native @@ -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 []] \ No newline at end of file +[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 []] diff --git a/tests/odt/native/referenceToText.native b/tests/odt/native/referenceToText.native index 45f7ac44c..1d80e2d0d 100644 --- a/tests/odt/native/referenceToText.native +++ b/tests/odt/native/referenceToText.native @@ -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 "."]] \ No newline at end of file +[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 "."]] diff --git a/tests/opml-reader.native b/tests/opml-reader.native index 14aff2c03..0819116ab 100644 --- a/tests/opml-reader.native +++ b/tests/opml-reader.native @@ -7,7 +7,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "Dave",Spa ,Header 3 ("",[],[]) [Strong [Str "Nevada"]] ,Para [Str "I",Space,Str "lived",Space,Str "here",Space,Emph [Str "once"],Str "."] ,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 "Ely"] ,Header 4 ("",[],[]) [Str "Gerlach"] diff --git a/tests/rst-reader.native b/tests/rst-reader.native index a3b462d8b..6b52c5728 100644 --- a/tests/rst-reader.native +++ b/tests/rst-reader.native @@ -210,12 +210,12 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Str "Plus:",Space,Str "+"] ,Para [Str "Minus:",Space,Str "-"] ,Header 1 ("links",[],[]) [Str "Links"] -,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 "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,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 "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 "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,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 "But",Space,Str "not",Space,Str "here:"] ,CodeBlock ("",[],[]) "http://example.com/" ,Header 1 ("images",[],[]) [Str "Images"] @@ -223,7 +223,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Image ("",[],[]) [Str "image"] ("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 "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"] ,Para [Str "First",Space,Str "paragraph"] ,Para [Str "Another",Space,Str "paragraph"] diff --git a/tests/testsuite.native b/tests/testsuite.native index 760729b0c..ba0bbb9c8 100644 --- a/tests/testsuite.native +++ b/tests/testsuite.native @@ -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."] ,HorizontalRule ,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 4 ("level-4",[],[]) [Str "Level",Space,Str "4"] ,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"] @@ -276,7 +276,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,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,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 [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."]]] @@ -292,7 +292,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 "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 [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 "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."] @@ -348,42 +348,42 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,HorizontalRule ,Header 1 ("links",[],[]) [Str "Links"] ,Header 2 ("explicit",[],[]) [Str "Explicit"] -,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 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 with \"quotes\" in it")] -,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 "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")] -,Para [Link [Str "Empty"] ("",""),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 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 with \"quotes\" in it")] +,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 "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")] +,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."] ,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 "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 [Str "Indented",Space,Link [Str "once"] ("/url",""),Str "."] -,Para [Str "Indented",Space,Link [Str "twice"] ("/url",""),Str "."] -,Para [Str "Indented",Space,Link [Str "thrice"] ("/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 [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 "twice"] ("/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."] ,CodeBlock ("",[],[]) "[not]: /url" -,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 "bar"] ("/url/","Title with \"quotes\" inside"),Str "."] +,Para [Str "Foo",Space,Link ("",[],[]) [Str "biz"] ("/url/","Title with \"quote\" inside"),Str "."] ,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,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",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?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 "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 "."] ,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 [[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."]]] -,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 - [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 ("",[],[]) ""] ,CodeBlock ("",[],[]) "or here: " ,HorizontalRule @@ -393,7 +393,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [Str "movie"] ("movie.jpg",""),Space,Str "icon."] ,HorizontalRule ,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 ("",[],[]) " { }",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 ("",[],[]) " { }",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 [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) diff --git a/tests/textile-reader.native b/tests/textile-reader.native index 18198ed60..0b5fceb0e 100644 --- a/tests/textile-reader.native +++ b/tests/textile-reader.native @@ -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\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."] ,HorizontalRule ,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 4 ("level-4",[],[]) [Str "Level",Space,Str "4"] ,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"] @@ -84,7 +84,7 @@ Pandoc (Meta {unMeta = fromList []}) ,([Str "beer"], [[Plain [Str "fresh",Space,Str "and",Space,Str "bitter"]]])] ,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 [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 "\8212",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,Quoted DoubleQuote [Str "I\8217d",Space,Str "like",Space,Str "to",Space,Str "thank",Space,Str "you"],Space,Str "for",Space,Str "example."] ,Header 1 ("links",[],[]) [Str "Links"] ,Header 2 ("explicit",[],[]) [Str "Explicit"] -,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 [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 [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 "Just",Space,Str "a",Space,Link ("",[],[]) [Str "url"] ("http://www.url.com","")] +,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 [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."] ,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 ":"] ,Header 2 ("without-headers",[],[]) [Str "Without",Space,Str "headers"] diff --git a/tests/twiki-reader.native b/tests/twiki-reader.native index 6e199a1a9..a3eb2cdc0 100644 --- a/tests/twiki-reader.native +++ b/tests/twiki-reader.native @@ -43,10 +43,10 @@ Pandoc (Meta {unMeta = fromList []}) ,Para [Str "With",Space,Str "two",Space,Str "paragraphs."]] ,Para [Str "Nother",Space,Str "paragraph."] ,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 [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 "email",Space,Str "me"] ("mailto:info@example.org","")] +,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://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 [Str "http://google.com"] ,Para [Str "http://google.com"] ,Para [Str "http://google.com"] diff --git a/tests/txt2tags.native b/tests/txt2tags.native index 382829e91..291c081ec 100644 --- a/tests/txt2tags.native +++ b/tests/txt2tags.native @@ -1,8 +1,8 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]),("date",MetaInlines [Str "date"]),("includeconf",MetaString "rules.conf"),("title",MetaInlines [Str "Txt2tags",Space,Str "Markup",Space,Str "Rules"])]}) [Para [Str "This",Space,Str "document",Space,Str "describes",Space,Str "all",Space,Str "the",Space,Str "details",Space,Str "about",Space,Str "each",Space,Str "txt2tags",Space,Str "mark.",Space,Str "The",Space,Str "target",Space,Str "audience",Space,Str "are",Space,Strong [Str "experienced"],Space,Str "users.",Space,Str "You",Space,Str "may",Space,Str "find",Space,Str "it",Space,Str "useful",Space,Str "if",Space,Str "you",Space,Str "want",Space,Str "to",Space,Str "master",Space,Str "the",Space,Str "marks",Space,Str "or",Space,Str "solve",Space,Str "a",Space,Str "specific",Space,Str "problem",Space,Str "about",Space,Str "a",Space,Str "mark."] -,Para [Str "If",Space,Str "you",Space,Str "are",Space,Str "new",Space,Str "to",Space,Str "txt2tags",Space,Str "or",Space,Str "just",Space,Str "want",Space,Str "to",Space,Str "know",Space,Str "which",Space,Str "are",Space,Str "the",Space,Str "available",Space,Str "marks,",Space,Str "please",Space,Str "read",Space,Str "the",Space,Link [Str "Markup",Space,Str "Demo"] ("MARKUPDEMO",""),Str "."] +,Para [Str "If",Space,Str "you",Space,Str "are",Space,Str "new",Space,Str "to",Space,Str "txt2tags",Space,Str "or",Space,Str "just",Space,Str "want",Space,Str "to",Space,Str "know",Space,Str "which",Space,Str "are",Space,Str "the",Space,Str "available",Space,Str "marks,",Space,Str "please",Space,Str "read",Space,Str "the",Space,Link ("",[],[]) [Str "Markup",Space,Str "Demo"] ("MARKUPDEMO",""),Str "."] ,Para [Str "Note",Space,Str "1:",Space,Str "This",Space,Str "document",Space,Str "is",Space,Str "generated",Space,Str "directly",Space,Str "from",Space,Str "the",Space,Str "txt2tags",Space,Str "test-suite.",Space,Str "All",Space,Str "the",Space,Str "rules",Space,Str "mentioned",Space,Str "here",Space,Str "are",Space,Str "100%",Space,Str "in",Space,Str "sync",Space,Str "with",Space,Str "the",Space,Str "current",Space,Str "program",Space,Str "code."] -,Para [Str "Note",Space,Str "2:",Space,Str "A",Space,Str "good",Space,Str "practice",Space,Str "is",Space,Str "to",Space,Str "consult",Space,Link [Str "the",Space,Str "sources"] ("rules.t2t",""),Space,Str "when",Space,Str "reading,",Space,Str "to",Space,Str "see",Space,Str "how",Space,Str "the",Space,Str "texts",Space,Str "were",Space,Str "made."] +,Para [Str "Note",Space,Str "2:",Space,Str "A",Space,Str "good",Space,Str "practice",Space,Str "is",Space,Str "to",Space,Str "consult",Space,Link ("",[],[]) [Str "the",Space,Str "sources"] ("rules.t2t",""),Space,Str "when",Space,Str "reading,",Space,Str "to",Space,Str "see",Space,Str "how",Space,Str "the",Space,Str "texts",Space,Str "were",Space,Str "made."] ,Para [Str "Table",Space,Str "of",Space,Str "Contents:"] ,HorizontalRule ,Header 1 ("paragraph",[],[]) [Str "Paragraph"] @@ -34,10 +34,10 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]] ,Para [Str "i)",Space,Str "****",Space,Str "////",Space,Str "____",Space,Str "----",Space,Str "````",Space,Str "\"\"\"\"",Space,Str "''''",Space,Str "i)",Space,Str "**",Space,Str "**",Space,Str "//",Space,Str "//",Space,Str "__",Space,Str "__",Space,Str "--",Space,Str "--",Space,Str "``",Space,Str "``",Space,Str "\"\"",Space,Str "\"\"",Space,Str "''",Space,Str "''"] ,Para [Str "i)",Space,Str "**",Space,Str "bold**",Space,Str "//",Space,Str "ital//",Space,Str "__",Space,Str "undr__",Space,Str "--",Space,Str "strk--",Space,Str "``",Space,Str "mono``",Space,Str "\"\"",Space,Str "raw\"\"",Space,Str "''",Space,Str "tggd''",Space,Str "i)",Space,Str "**bold",Space,Str "**",Space,Str "//ital",Space,Str "//",Space,Str "__undr",Space,Str "__",Space,Str "--strk",Space,Str "--",Space,Str "``mono",Space,Str "``",Space,Str "\"\"raw",Space,Str "\"\"",Space,Str "''tggd",Space,Str "''",Space,Str "i)",Space,Str "**",Space,Str "bold",Space,Str "**",Space,Str "//",Space,Str "ital",Space,Str "//",Space,Str "__",Space,Str "undr",Space,Str "__",Space,Str "--",Space,Str "strk",Space,Str "--",Space,Str "``",Space,Str "mono",Space,Str "``",Space,Str "\"\"",Space,Str "raw",Space,Str "\"\"",Space,Str "''",Space,Str "tggd",Space,Str "''"] ,Header 1 ("link",[],[]) [Str "Link"] -,Para [Link [Str "mailto:user@domain.com"] ("user@domain.com",""),Space,Link [Str "mailto:user@domain.com"] ("user@domain.com",""),Str ".",Space,Link [Str "mailto:user@domain.com"] ("user@domain.com",""),Str ".",Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "mailto:user@domain.com"] ("user@domain.com",""),Str ".",Space,Str "any",Space,Str "text.",Space,Link [Str "label"] ("user@domain.com",""),Space,Link [Str "mailto:user@domain.com?subject=bla"] ("user@domain.com?subject=bla",""),Space,Link [Str "mailto:user@domain.com?subject=bla"] ("user@domain.com?subject=bla",""),Str ".",Space,Link [Str "mailto:user@domain.com?subject=bla"] ("user@domain.com?subject=bla",""),Str ",",Space,Link [Str "mailto:user@domain.com?subject=bla&cc=otheruser@domain.com"] ("user@domain.com?subject=bla&cc=otheruser@domain.com",""),Space,Link [Str "mailto:user@domain.com?subject=bla&cc=otheruser@domain.com"] ("user@domain.com?subject=bla&cc=otheruser@domain.com",""),Str ".",Space,Link [Str "mailto:user@domain.com?subject=bla&cc=otheruser@domain.com"] ("user@domain.com?subject=bla&cc=otheruser@domain.com",""),Str ",",Space,Link [Str "label"] ("user@domain.com?subject=bla&cc=otheruser@domain.com",""),Str ".",Space,Link [Str "label"] ("user@domain.com?subject=bla&cc=otheruser@domain.com.",""),Str ".",Space,Link [Str "http://www.domain.com"] ("http://www.domain.com",""),Space,Link [Str "http://www.domain.com/dir/"] ("http://www.domain.com/dir/",""),Space,Link [Str "http://www.domain.com/dir///"] ("http://www.domain.com/dir///",""),Space,Link [Str "http://www.domain.com."] ("http://www.domain.com.",""),Space,Link [Str "http://www.domain.com,"] ("http://www.domain.com,",""),Space,Link [Str "http://www.domain.com."] ("http://www.domain.com.",""),Space,Str "any",Space,Str "text.",Space,Link [Str "http://www.domain.com,"] ("http://www.domain.com,",""),Space,Str "any",Space,Str "text.",Space,Link [Str "http://www.domain.com/dir/."] ("http://www.domain.com/dir/.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "http://www.domain.com."] ("http://www.domain.com.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "http://www.domain.com/dir/."] ("http://www.domain.com/dir/.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "http://www.domain.com/dir/index.html."] ("http://www.domain.com/dir/index.html.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "http://www.domain.com/dir/index.html,"] ("http://www.domain.com/dir/index.html,",""),Space,Str "any",Space,Str "text.",Space,Link [Str "http://www.domain.com/dir/#anchor"] ("http://www.domain.com/dir/#anchor",""),Space,Link [Str "http://www.domain.com/dir/index.html#anchor"] ("http://www.domain.com/dir/index.html#anchor",""),Space,Link [Str "http://www.domain.com/dir/index.html#anchor."] ("http://www.domain.com/dir/index.html#anchor.",""),Space,Link [Str "http://www.domain.com/dir/#anchor."] ("http://www.domain.com/dir/#anchor.",""),Space,Str "any",Space,Str "text.",Space,Link [Str "http://www.domain.com/dir/index.html#anchor."] ("http://www.domain.com/dir/index.html#anchor.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "http://www.domain.com/dir/#anchor."] ("http://www.domain.com/dir/#anchor.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link [Str "http://www.domain.com/dir/index.html#anchor."] ("http://www.domain.com/dir/index.html#anchor.",""),Space,Str "any",Space,Str "text.",Space,Link [Str "http://domain.com?a=a@a.a&b=a+b+c."] ("http://domain.com?a=a@a.a&b=a+b+c.",""),Space,Link [Str "http://domain.com?a=a@a.a&b=a+b+c,"] ("http://domain.com?a=a@a.a&b=a+b+c,",""),Space,Link [Str "http://domain.com/bla.cgi?a=a@a.a&b=a+b+c."] ("http://domain.com/bla.cgi?a=a@a.a&b=a+b+c.",""),Space,Link [Str "http://domain.com/bla.cgi?a=a@a.a&b=a+b+c@."] ("http://domain.com/bla.cgi?a=a@a.a&b=a+b+c@.",""),Space,Link [Str "http://domain.com?a=a@a.a&b=a+b+c.#anchor"] ("http://domain.com?a=a@a.a&b=a+b+c.#anchor",""),Space,Link [Str "http://domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor"] ("http://domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor",""),Space,Link [Str "http://domain.com/bla.cgi?a=a@a.a&b=a+b+c@.#anchor"] ("http://domain.com/bla.cgi?a=a@a.a&b=a+b+c@.#anchor",""),Space,Link [Str "http://user:password@domain.com/bla.html."] ("http://user:password@domain.com/bla.html.",""),Space,Link [Str "http://user:password@domain.com/dir/."] ("http://user:password@domain.com/dir/.",""),Space,Link [Str "http://user:password@domain.com."] ("http://user:password@domain.com.",""),Space,Link [Str "http://user:@domain.com."] ("http://user:@domain.com.",""),Space,Link [Str "http://user@domain.com."] ("http://user@domain.com.",""),Space,Link [Str "http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor"] ("http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor",""),Space,Link [Str "http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c@#anchor"] ("http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c@#anchor",""),Space,Link [Str "label"] ("www.domain.com",""),Space,Str "[",Space,Str "label",Space,Link [Str "www.domain.com"] ("www.domain.com",""),Str "]",Space,Link [Str "label",Space] ("www.domain.com",""),Space,Link [Str "anchor",Space] ("http://www.domain.com/dir/index.html#anchor.",""),Space,Link [Str "login",Space] ("http://user:password@domain.com/bla.html",""),Space,Link [Str "form",Space] ("http://www.domain.com/bla.cgi?a=a@a.a&b=a+b+c.",""),Space,Link [Str "form",Space,Str "&",Space,Str "anchor"] ("http://www.domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor",""),Space,Link [Str "login",Space,Str "&",Space,Str "form",Space] ("http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c.",""),Space,Link [Str "local",Space,Str "link",Space,Str "up",Space] ("..",""),Space,Link [Str "local",Space,Str "link",Space,Str "file",Space] ("bla.html",""),Space,Link [Str "local",Space,Str "link",Space,Str "anchor",Space] ("#anchor",""),Space,Link [Str "local",Space,Str "link",Space,Str "file/anchor"] ("bla.html#anchor",""),Space,Link [Str "local",Space,Str "link",Space,Str "file/anchor"] ("bla.html#anchor.",""),Space,Link [Str "local",Space,Str "link",Space,Str "img",Space] ("abc.gif",""),Space,Link [Str "www.fake.com"] ("www.domain.com",""),Space,Link [Str "http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm"] ("http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm",""),Space,Link [Str "http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-"] ("http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-",""),Space,Link [Str "http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_"] ("http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_",""),Str "-1%.",Space,Link [Str "http://foo._user-9:pass!#$%&*()+word@domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_"] ("http://foo._user-9:pass!#$%&*()+word@domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_",""),Str "-1%.",Space,Link [Str "http://L1.com"] ("http://L1.com",""),Space,Str "!",Space,Link [Str "mailto:L2@www.com"] ("L2@www.com",""),Space,Str "!",Space,Link [Str "L3"] ("www.com",""),Space,Str "!",Space,Link [Str "L4"] ("w@ww.com",""),Space,Str "!",Space,Link [Str "www.L5.com"] ("www.L5.com",""),Space,Link [Str "www.domain.com"] ("www.domain.com",""),Space,Link [Str "www2.domain.com"] ("www2.domain.com",""),Space,Link [Str "ftp.domain.com"] ("ftp.domain.com",""),Space,Link [Str "WWW.DOMAIN.COM"] ("WWW.DOMAIN.COM",""),Space,Link [Str "FTP.DOMAIN.COM"] ("FTP.DOMAIN.COM",""),Space,Link [Str "label"] ("www.domain.com",""),Space,Link [Str "label"] ("ftp.domain.com",""),Space,Link [Str "label"] ("WWW.DOMAIN.COM",""),Space,Link [Str "label"] ("FTP.DOMAIN.COM",""),Space,Str "[label",Space,Link [Str "www.domain.com"] ("www.domain.com",""),Space,Str "]",Space,Str "[label]",Space,Link [Str "www.domain.com"] ("www.domain.com",""),Str "]"] +,Para [Link ("",[],[]) [Str "mailto:user@domain.com"] ("user@domain.com",""),Space,Link ("",[],[]) [Str "mailto:user@domain.com"] ("user@domain.com",""),Str ".",Space,Link ("",[],[]) [Str "mailto:user@domain.com"] ("user@domain.com",""),Str ".",Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link ("",[],[]) [Str "mailto:user@domain.com"] ("user@domain.com",""),Str ".",Space,Str "any",Space,Str "text.",Space,Link ("",[],[]) [Str "label"] ("user@domain.com",""),Space,Link ("",[],[]) [Str "mailto:user@domain.com?subject=bla"] ("user@domain.com?subject=bla",""),Space,Link ("",[],[]) [Str "mailto:user@domain.com?subject=bla"] ("user@domain.com?subject=bla",""),Str ".",Space,Link ("",[],[]) [Str "mailto:user@domain.com?subject=bla"] ("user@domain.com?subject=bla",""),Str ",",Space,Link ("",[],[]) [Str "mailto:user@domain.com?subject=bla&cc=otheruser@domain.com"] ("user@domain.com?subject=bla&cc=otheruser@domain.com",""),Space,Link ("",[],[]) [Str "mailto:user@domain.com?subject=bla&cc=otheruser@domain.com"] ("user@domain.com?subject=bla&cc=otheruser@domain.com",""),Str ".",Space,Link ("",[],[]) [Str "mailto:user@domain.com?subject=bla&cc=otheruser@domain.com"] ("user@domain.com?subject=bla&cc=otheruser@domain.com",""),Str ",",Space,Link ("",[],[]) [Str "label"] ("user@domain.com?subject=bla&cc=otheruser@domain.com",""),Str ".",Space,Link ("",[],[]) [Str "label"] ("user@domain.com?subject=bla&cc=otheruser@domain.com.",""),Str ".",Space,Link ("",[],[]) [Str "http://www.domain.com"] ("http://www.domain.com",""),Space,Link ("",[],[]) [Str "http://www.domain.com/dir/"] ("http://www.domain.com/dir/",""),Space,Link ("",[],[]) [Str "http://www.domain.com/dir///"] ("http://www.domain.com/dir///",""),Space,Link ("",[],[]) [Str "http://www.domain.com."] ("http://www.domain.com.",""),Space,Link ("",[],[]) [Str "http://www.domain.com,"] ("http://www.domain.com,",""),Space,Link ("",[],[]) [Str "http://www.domain.com."] ("http://www.domain.com.",""),Space,Str "any",Space,Str "text.",Space,Link ("",[],[]) [Str "http://www.domain.com,"] ("http://www.domain.com,",""),Space,Str "any",Space,Str "text.",Space,Link ("",[],[]) [Str "http://www.domain.com/dir/."] ("http://www.domain.com/dir/.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link ("",[],[]) [Str "http://www.domain.com."] ("http://www.domain.com.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link ("",[],[]) [Str "http://www.domain.com/dir/."] ("http://www.domain.com/dir/.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link ("",[],[]) [Str "http://www.domain.com/dir/index.html."] ("http://www.domain.com/dir/index.html.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link ("",[],[]) [Str "http://www.domain.com/dir/index.html,"] ("http://www.domain.com/dir/index.html,",""),Space,Str "any",Space,Str "text.",Space,Link ("",[],[]) [Str "http://www.domain.com/dir/#anchor"] ("http://www.domain.com/dir/#anchor",""),Space,Link ("",[],[]) [Str "http://www.domain.com/dir/index.html#anchor"] ("http://www.domain.com/dir/index.html#anchor",""),Space,Link ("",[],[]) [Str "http://www.domain.com/dir/index.html#anchor."] ("http://www.domain.com/dir/index.html#anchor.",""),Space,Link ("",[],[]) [Str "http://www.domain.com/dir/#anchor."] ("http://www.domain.com/dir/#anchor.",""),Space,Str "any",Space,Str "text.",Space,Link ("",[],[]) [Str "http://www.domain.com/dir/index.html#anchor."] ("http://www.domain.com/dir/index.html#anchor.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link ("",[],[]) [Str "http://www.domain.com/dir/#anchor."] ("http://www.domain.com/dir/#anchor.",""),Space,Str "any",Space,Str "text.",Space,Str "any",Space,Str "text:",Space,Link ("",[],[]) [Str "http://www.domain.com/dir/index.html#anchor."] ("http://www.domain.com/dir/index.html#anchor.",""),Space,Str "any",Space,Str "text.",Space,Link ("",[],[]) [Str "http://domain.com?a=a@a.a&b=a+b+c."] ("http://domain.com?a=a@a.a&b=a+b+c.",""),Space,Link ("",[],[]) [Str "http://domain.com?a=a@a.a&b=a+b+c,"] ("http://domain.com?a=a@a.a&b=a+b+c,",""),Space,Link ("",[],[]) [Str "http://domain.com/bla.cgi?a=a@a.a&b=a+b+c."] ("http://domain.com/bla.cgi?a=a@a.a&b=a+b+c.",""),Space,Link ("",[],[]) [Str "http://domain.com/bla.cgi?a=a@a.a&b=a+b+c@."] ("http://domain.com/bla.cgi?a=a@a.a&b=a+b+c@.",""),Space,Link ("",[],[]) [Str "http://domain.com?a=a@a.a&b=a+b+c.#anchor"] ("http://domain.com?a=a@a.a&b=a+b+c.#anchor",""),Space,Link ("",[],[]) [Str "http://domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor"] ("http://domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor",""),Space,Link ("",[],[]) [Str "http://domain.com/bla.cgi?a=a@a.a&b=a+b+c@.#anchor"] ("http://domain.com/bla.cgi?a=a@a.a&b=a+b+c@.#anchor",""),Space,Link ("",[],[]) [Str "http://user:password@domain.com/bla.html."] ("http://user:password@domain.com/bla.html.",""),Space,Link ("",[],[]) [Str "http://user:password@domain.com/dir/."] ("http://user:password@domain.com/dir/.",""),Space,Link ("",[],[]) [Str "http://user:password@domain.com."] ("http://user:password@domain.com.",""),Space,Link ("",[],[]) [Str "http://user:@domain.com."] ("http://user:@domain.com.",""),Space,Link ("",[],[]) [Str "http://user@domain.com."] ("http://user@domain.com.",""),Space,Link ("",[],[]) [Str "http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor"] ("http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor",""),Space,Link ("",[],[]) [Str "http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c@#anchor"] ("http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c@#anchor",""),Space,Link ("",[],[]) [Str "label"] ("www.domain.com",""),Space,Str "[",Space,Str "label",Space,Link ("",[],[]) [Str "www.domain.com"] ("www.domain.com",""),Str "]",Space,Link ("",[],[]) [Str "label",Space] ("www.domain.com",""),Space,Link ("",[],[]) [Str "anchor",Space] ("http://www.domain.com/dir/index.html#anchor.",""),Space,Link ("",[],[]) [Str "login",Space] ("http://user:password@domain.com/bla.html",""),Space,Link ("",[],[]) [Str "form",Space] ("http://www.domain.com/bla.cgi?a=a@a.a&b=a+b+c.",""),Space,Link ("",[],[]) [Str "form",Space,Str "&",Space,Str "anchor"] ("http://www.domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor",""),Space,Link ("",[],[]) [Str "login",Space,Str "&",Space,Str "form",Space] ("http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c.",""),Space,Link ("",[],[]) [Str "local",Space,Str "link",Space,Str "up",Space] ("..",""),Space,Link ("",[],[]) [Str "local",Space,Str "link",Space,Str "file",Space] ("bla.html",""),Space,Link ("",[],[]) [Str "local",Space,Str "link",Space,Str "anchor",Space] ("#anchor",""),Space,Link ("",[],[]) [Str "local",Space,Str "link",Space,Str "file/anchor"] ("bla.html#anchor",""),Space,Link ("",[],[]) [Str "local",Space,Str "link",Space,Str "file/anchor"] ("bla.html#anchor.",""),Space,Link ("",[],[]) [Str "local",Space,Str "link",Space,Str "img",Space] ("abc.gif",""),Space,Link ("",[],[]) [Str "www.fake.com"] ("www.domain.com",""),Space,Link ("",[],[]) [Str "http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm"] ("http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm",""),Space,Link ("",[],[]) [Str "http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-"] ("http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-",""),Space,Link ("",[],[]) [Str "http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_"] ("http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_",""),Str "-1%.",Space,Link ("",[],[]) [Str "http://foo._user-9:pass!#$%&*()+word@domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_"] ("http://foo._user-9:pass!#$%&*()+word@domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_",""),Str "-1%.",Space,Link ("",[],[]) [Str "http://L1.com"] ("http://L1.com",""),Space,Str "!",Space,Link ("",[],[]) [Str "mailto:L2@www.com"] ("L2@www.com",""),Space,Str "!",Space,Link ("",[],[]) [Str "L3"] ("www.com",""),Space,Str "!",Space,Link ("",[],[]) [Str "L4"] ("w@ww.com",""),Space,Str "!",Space,Link ("",[],[]) [Str "www.L5.com"] ("www.L5.com",""),Space,Link ("",[],[]) [Str "www.domain.com"] ("www.domain.com",""),Space,Link ("",[],[]) [Str "www2.domain.com"] ("www2.domain.com",""),Space,Link ("",[],[]) [Str "ftp.domain.com"] ("ftp.domain.com",""),Space,Link ("",[],[]) [Str "WWW.DOMAIN.COM"] ("WWW.DOMAIN.COM",""),Space,Link ("",[],[]) [Str "FTP.DOMAIN.COM"] ("FTP.DOMAIN.COM",""),Space,Link ("",[],[]) [Str "label"] ("www.domain.com",""),Space,Link ("",[],[]) [Str "label"] ("ftp.domain.com",""),Space,Link ("",[],[]) [Str "label"] ("WWW.DOMAIN.COM",""),Space,Link ("",[],[]) [Str "label"] ("FTP.DOMAIN.COM",""),Space,Str "[label",Space,Link ("",[],[]) [Str "www.domain.com"] ("www.domain.com",""),Space,Str "]",Space,Str "[label]",Space,Link ("",[],[]) [Str "www.domain.com"] ("www.domain.com",""),Str "]"] ,Header 1 ("image",[],[]) [Str "Image"] ,Para [Image ("",[],[]) [] ("img.png","")] -,Para [Link [Image ("",[],[]) [] ("img.png","")] ("http://txt2tags.org","")] +,Para [Link ("",[],[]) [Image ("",[],[]) [] ("img.png","")] ("http://txt2tags.org","")] ,Para [Image ("",[],[]) [] ("img.png",""),Space,Str "Image",Space,Str "at",Space,Str "the",Space,Str "line",Space,Str "beginning."] ,Para [Str "Image",Space,Str "in",Space,Str "the",Space,Str "middle",Space,Image ("",[],[]) [] ("img.png",""),Space,Str "of",Space,Str "the",Space,Str "line."] ,Para [Str "Image",Space,Str "at",Space,Str "the",Space,Str "line",Space,Str "end.",Space,Image ("",[],[]) [] ("img.png","")] @@ -159,7 +159,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]] ,([Str "Start",Space,Str "term",Space,Str "with",Space,Str "colon"], [[Plain [Str "And",Space,Str "its",Space,Str "definition",Space,Str "follows"]]])] ,Header 1 ("numlist",[],[]) [Str "Numbered",Space,Str "List"] -,Para [Str "See",Space,Link [Str "List"] ("#list",""),Str ",",Space,Str "the",Space,Str "same",Space,Str "rules",Space,Str "apply."] +,Para [Str "See",Space,Link ("",[],[]) [Str "List"] ("#list",""),Str ",",Space,Str "the",Space,Str "same",Space,Str "rules",Space,Str "apply."] ,Header 1 ("list",[],[]) [Str "List"] ,BulletList [[Plain [Str "Use",Space,Str "the",Space,Str "hyphen",Space,Str "to",Space,Str "prefix",Space,Str "list",Space,Str "items."]] diff --git a/tests/writer.native b/tests/writer.native index 760729b0c..ba0bbb9c8 100644 --- a/tests/writer.native +++ b/tests/writer.native @@ -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."] ,HorizontalRule ,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 4 ("level-4",[],[]) [Str "Level",Space,Str "4"] ,Header 5 ("level-5",[],[]) [Str "Level",Space,Str "5"] @@ -276,7 +276,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,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,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 [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."]]] @@ -292,7 +292,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 "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 [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 "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."] @@ -348,42 +348,42 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,HorizontalRule ,Header 1 ("links",[],[]) [Str "Links"] ,Header 2 ("explicit",[],[]) [Str "Explicit"] -,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 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 with \"quotes\" in it")] -,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 "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")] -,Para [Link [Str "Empty"] ("",""),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 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 with \"quotes\" in it")] +,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 "Email",Space,Str "link"] ("mailto:nobody@nowhere.net","")] +,Para [Link ("",[],[]) [Str "Empty"] ("",""),Str "."] ,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 "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 [Str "Indented",Space,Link [Str "once"] ("/url",""),Str "."] -,Para [Str "Indented",Space,Link [Str "twice"] ("/url",""),Str "."] -,Para [Str "Indented",Space,Link [Str "thrice"] ("/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 [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 "twice"] ("/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."] ,CodeBlock ("",[],[]) "[not]: /url" -,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 "bar"] ("/url/","Title with \"quotes\" inside"),Str "."] +,Para [Str "Foo",Space,Link ("",[],[]) [Str "biz"] ("/url/","Title with \"quote\" inside"),Str "."] ,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,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",Space,Str "in",Space,Str "pointy",Space,Str "braces"] ("/script?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 "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 "."] ,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 [[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."]]] -,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 - [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 ("",[],[]) ""] ,CodeBlock ("",[],[]) "or here: " ,HorizontalRule @@ -393,7 +393,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa ,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [Str "movie"] ("movie.jpg",""),Space,Str "icon."] ,HorizontalRule ,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 ("",[],[]) " { }",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 ("",[],[]) " { }",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 [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)