diff options
47 files changed, 3463 insertions, 587 deletions
@@ -14,7 +14,7 @@ Pandoc is a [Haskell] library for converting from one markup format to another, and a command-line tool that uses this library. It can read [markdown] and (subsets of) [Textile], [reStructuredText], [HTML], [LaTeX], [MediaWiki markup], [Haddock markup], [OPML], [Emacs -Org-mode], [DocBook], and [Word docx]; and it can write plain text, +Org-mode], [DocBook], [txt2tags] and [Word docx]; and it can write plain text, [markdown], [reStructuredText], [XHTML], [HTML 5], [LaTeX] (including [beamer] slide shows), [ConTeXt], [RTF], [OPML], [DocBook], [OpenDocument], [ODT], [Word docx], [GNU Texinfo], [MediaWiki markup], @@ -144,9 +144,9 @@ General options `markdown_phpextra` (PHP Markdown Extra extended markdown), `markdown_github` (github extended markdown), `textile` (Textile), `rst` (reStructuredText), `html` (HTML), - `docbook` (DocBook), `opml` (OPML), `org` (Emacs Org-mode), - `mediawiki` (MediaWiki markup), `haddock` (Haddock markup), or - `latex` (LaTeX). If `+lhs` is appended to `markdown`, `rst`, + `docbook` (DocBook), `t2t` (txt2tags), `opml` (OPML), `org` (Emacs + Org-mode), `mediawiki` (MediaWiki markup), `haddock` (Haddock markup), + or `latex` (LaTeX). If `+lhs` is appended to `markdown`, `rst`, `latex`, or `html`, the input will be treated as literate Haskell source: see [Literate Haskell support](#literate-haskell-support), below. Markdown syntax extensions can be individually enabled or @@ -318,7 +318,13 @@ Reader options classes, respectively. The author and time of change is included. *all* is useful for scripting: only accepting changes from a certain reviewer, say, or before a certain date. This - option only affects the Docx reader. + option only affects the docx reader. + +`--extract-media=`*DIR* +: Extract images and other media contained in a docx or epub container + to the path *DIR*, creating it if necessary, and adjust the images + references in the document so they point to the extracted files. + This option only affects the docx and epub readers. General writer options ---------------------- @@ -541,9 +547,9 @@ Options affecting specific writers for a file `reference.docx` in the user data directory (see `--data-dir`). If this is not found either, sensible defaults will be used. The following styles are used by pandoc: [paragraph] - Normal, Compact, Title, Authors, Date, Heading 1, Heading 2, Heading 3, - Heading 4, Heading 5, Block Quote, Definition Term, Definition, - Body Text, Table Caption, Image Caption; [character] Default + Normal, Compact, Title, Subtitle, Authors, Date, Abstract, Heading 1, + Heading 2, Heading 3, Heading 4, Heading 5, Block Quote, Definition Term, + Definition, Body Text, Table Caption, Image Caption; [character] Default Paragraph Font, Body Text Char, Verbatim Char, Footnote Ref, Link. @@ -1764,7 +1770,10 @@ legal (though ugly) pipe table: orange|3.09 The cells of pipe tables cannot contain block elements like paragraphs -and lists, and cannot span multiple lines. +and lists, and cannot span multiple lines. Note also that in LaTeX/PDF +output, the cells produced by pipe tables will not wrap, since there +is no information available about relative widths. If you want content +to wrap within cells, use multiline or grid tables. [the same as in PHP markdown extra]: http://michelf.ca/projects/php-markdown/extra/#table @@ -3100,3 +3109,4 @@ Rosenthal. [marc relators]: http://www.loc.gov/marc/relators/relaterm.html [RFC5646]: http://tools.ietf.org/html/rfc5646 [InDesign ICML]: https://www.adobe.com/content/dam/Adobe/en/devnet/indesign/cs55-docs/IDML/idml-specification.pdf +[txt2tags]: http://txt2tags.org/ diff --git a/benchmark/benchmark-pandoc.hs b/benchmark/benchmark-pandoc.hs index 9238b09d7..bf67eaa4d 100644 --- a/benchmark/benchmark-pandoc.hs +++ b/benchmark/benchmark-pandoc.hs @@ -20,19 +20,18 @@ import Criterion.Main import Criterion.Config import System.Environment (getArgs) import Data.Monoid +import Data.Maybe (mapMaybe) +import Debug.Trace (trace) readerBench :: Pandoc -> (String, ReaderOptions -> String -> IO Pandoc) - -> Benchmark -readerBench doc (name, reader) = - let writer = case lookup name writers of - Just (PureStringWriter w) -> w - _ -> error $ "Could not find writer for " ++ name - inp = writer def{ writerWrapText = True } doc - -- we compute the length to force full evaluation - getLength (Pandoc (Meta _) d) = length d - in bench (name ++ " reader") $ whnfIO $ getLength `fmap` - (reader def{ readerSmart = True }) inp + -> Maybe Benchmark +readerBench doc (name, reader) = case lookup name writers of + Just (PureStringWriter writer) -> + let inp = writer def{ writerWrapText = True} doc + in return $ bench (name ++ " reader") $ nfIO $ + (reader def{ readerSmart = True }) inp + _ -> trace ("\nCould not find writer for " ++ name ++ "\n") Nothing writerBench :: Pandoc -> (String, WriterOptions -> Pandoc -> String) @@ -43,13 +42,16 @@ writerBench doc (name, writer) = bench (name ++ " writer") $ nf main :: IO () main = do args <- getArgs - (conf,_) <- parseArgs defaultConfig{ cfgSamples = Last $ Just 20 } defaultOptions args - inp <- readFile "README" - inp2 <- readFile "tests/testsuite.txt" + (conf,_) <- parseArgs defaultConfig{ cfgSamples = Last $ Just 20 } + defaultOptions args + inp <- readFile "tests/testsuite.txt" let opts = def{ readerSmart = True } - let doc = readMarkdown opts $ inp ++ unlines (drop 3 $ lines inp2) - let readerBs = map (readerBench doc) - $ filter (\(n,_) -> n /="haddock") readers + let doc = readMarkdown opts inp + let readers' = [(n,r) | (n, StringReader r) <- readers] + let readerBs = mapMaybe (readerBench doc) + $ filter (\(n,_) -> n /="haddock") readers' let writers' = [(n,w) | (n, PureStringWriter w) <- writers] + let writerBs = map (writerBench doc) + $ writers' defaultMainWith conf (return ()) $ - map (writerBench doc) writers' ++ readerBs + writerBs ++ readerBs diff --git a/data/reference.docx b/data/reference.docx Binary files differindex 7efc62458..08059eb3c 100644 --- a/data/reference.docx +++ b/data/reference.docx diff --git a/pandoc.cabal b/pandoc.cabal index 08644d995..e507ac42f 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -17,7 +17,7 @@ Description: Pandoc is a Haskell library for converting from one markup format to another, and a command-line tool that uses this library. It can read markdown and (subsets of) HTML, reStructuredText, LaTeX, DocBook, MediaWiki markup, Haddock - markup, OPML, Emacs Org-Mode, and Textile, and it can write + markup, OPML, Emacs Org-Mode, txt2tags and Textile, and it can write markdown, reStructuredText, HTML, LaTeX, ConTeXt, Docbook, OPML, OpenDocument, ODT, Word docx, RTF, MediaWiki, DokuWiki, Textile, groff man pages, plain text, Emacs Org-Mode, AsciiDoc, @@ -94,34 +94,23 @@ Extra-Source-Files: -- tests tests/bodybg.gif, tests/docbook-reader.docbook - tests/docbook-reader.native tests/html-reader.html, - tests/html-reader.native, tests/opml-reader.opml, - tests/opml-reader.native, tests/haddock-reader.haddock, - tests/haddock-reader.native, tests/insert, tests/lalune.jpg, tests/movie.jpg, tests/latex-reader.latex, - tests/latex-reader.native, tests/textile-reader.textile, - tests/textile-reader.native, tests/markdown-reader-more.txt, - tests/markdown-reader-more.native, tests/markdown-citations.txt, - tests/markdown-citations.native, tests/textile-reader.textile, tests/mediawiki-reader.wiki, - tests/mediawiki-reader.native, - tests/rst-reader.native, tests/rst-reader.rst, tests/s5.basic.html, tests/s5.fancy.html, tests/s5.fragment.html, tests/s5.inserts.html, - tests/s5.native, tests/tables.context, tests/tables.docbook, tests/tables.html, @@ -131,7 +120,6 @@ Extra-Source-Files: tests/tables.markdown, tests/tables.mediawiki, tests/tables.textile, - tests/tables.native, tests/tables.opendocument, tests/tables.org, tests/tables.asciidoc, @@ -140,9 +128,7 @@ Extra-Source-Files: tests/tables.rst, tests/tables.rtf, tests/tables.txt, - tests/tables-rstsubset.native, tests/tables.fb2, - tests/testsuite.native, tests/testsuite.txt, tests/writer.latex, tests/writer.context, @@ -153,7 +139,6 @@ Extra-Source-Files: tests/writer.plain, tests/writer.mediawiki, tests/writer.textile, - tests/writer.native, tests/writer.opendocument, tests/writer.org, tests/writer.asciidoc, @@ -163,8 +148,6 @@ Extra-Source-Files: tests/writer.texinfo, tests/writer.fb2, tests/writer.opml, - tests/lhs-test.native, - tests/lhs-test-markdown.native, tests/lhs-test.markdown, tests/lhs-test.markdown+lhs, tests/lhs-test.rst, @@ -175,7 +158,6 @@ Extra-Source-Files: tests/lhs-test.html+lhs, tests/lhs-test.fragment.html+lhs, tests/pipe-tables.txt, - tests/pipe-tables.native, tests/fb2.basic.markdown, tests/fb2.basic.fb2, tests/fb2.titles.markdown, @@ -188,26 +170,30 @@ Extra-Source-Files: tests/fb2.math.fb2, tests/fb2.test-small.png, tests/fb2.test.jpg, - tests/docx.already_auto_ident.native, tests/docx.already_auto_ident.docx, tests/docx.block_quotes.docx, - tests/docx.block_quotes_parse_indent.native, + tests/docx.codeblock.docx, + tests/docx.deep_normalize.docx, + tests/docx.definition_list.docx, + tests/docx.hanging_indent.docx, tests/docx.headers.docx, - tests/docx.headers.native, tests/docx.image.docx, - tests/docx.image_no_embed.native, + tests/docx.inline_code.docx, tests/docx.inline_formatting.docx, - tests/docx.inline_formatting.native, tests/docx.links.docx, - tests/docx.links.native, tests/docx.lists.docx, - tests/docx.lists.native, + tests/docx.metadata.docx, + tests/docx.metadata_after_normal.docx, + tests/docx.normalize.docx, tests/docx.notes.docx, - tests/docx.notes.native, tests/docx.tables.docx, - tests/docx.tables.native, + tests/docx.tabs.docx, + tests/docx.track_changes_deletion.docx, + tests/docx.track_changes_insertion.docx, + tests/docx.trailing_spaces_in_formatting.docx, tests/docx.unicode.docx, - tests/docx.unicode.native + tests/*.native, + tests/txt2tags.t2t Extra-Tmp-Files: man/man1/pandoc.1, man/man5/pandoc_markdown.5 @@ -246,7 +232,7 @@ Library random >= 1 && < 1.1, extensible-exceptions >= 0.1 && < 0.2, pandoc-types >= 1.12.3.3 && < 1.13, - aeson >= 0.7 && < 0.8, + aeson >= 0.7 && < 0.9, tagsoup >= 0.13.1 && < 0.14, base64-bytestring >= 0.1 && < 1.1, zlib >= 0.5 && < 0.6, @@ -261,7 +247,8 @@ Library hslua >= 0.3 && < 0.4, binary >= 0.5 && < 0.8, SHA >= 1.6 && < 1.7, - haddock-library >= 1.1 && < 1.2 + haddock-library >= 1.1 && < 1.2, + old-time if flag(https) Build-Depends: http-client >= 0.3.2 && < 0.4, http-client-tls >= 0.2 && < 0.3, @@ -286,6 +273,7 @@ Library Text.Pandoc.Options, Text.Pandoc.Pretty, Text.Pandoc.Shared, + Text.Pandoc.MediaBag, Text.Pandoc.Readers.HTML, Text.Pandoc.Readers.LaTeX, Text.Pandoc.Readers.Markdown, @@ -328,7 +316,8 @@ Library Text.Pandoc.Templates, Text.Pandoc.XML, Text.Pandoc.SelfContained, - Text.Pandoc.Process + Text.Pandoc.Process, + Text.Pandoc.Readers.Txt2Tags Other-Modules: Text.Pandoc.Readers.Docx.Lists, Text.Pandoc.Readers.Docx.Reducible, Text.Pandoc.Readers.Docx.Parse, @@ -344,6 +333,7 @@ Library Text.Pandoc.Compat.Monoid, Text.Pandoc.Compat.Except, Text.Pandoc.Compat.TagSoupEntity, + Text.Pandoc.Compat.Directory Paths_pandoc Buildable: True @@ -359,7 +349,7 @@ Executable pandoc bytestring >= 0.9 && < 0.11, extensible-exceptions >= 0.1 && < 0.2, highlighting-kate >= 0.5.8.5 && < 0.6, - aeson >= 0.7.0.5 && < 0.8, + aeson >= 0.7.0.5 && < 0.9, yaml >= 0.8.8.2 && < 0.9, containers >= 0.1 && < 0.6, HTTP >= 4000.0.5 && < 4000.3 @@ -409,7 +399,8 @@ Test-Suite test-pandoc QuickCheck >= 2.4 && < 2.8, HUnit >= 1.2 && < 1.3, containers >= 0.1 && < 0.6, - ansi-terminal >= 0.5 && < 0.7 + ansi-terminal >= 0.5 && < 0.7, + zip-archive >= 0.2.3.2 && < 0.3 Other-Modules: Tests.Old Tests.Helpers Tests.Arbitrary @@ -420,10 +411,12 @@ Test-Suite test-pandoc Tests.Readers.Org Tests.Readers.RST Tests.Readers.Docx + Tests.Readers.Txt2Tags Tests.Writers.Native Tests.Writers.ConTeXt Tests.Writers.HTML Tests.Writers.Markdown + Tests.Writers.Plain Tests.Writers.AsciiDoc Tests.Writers.LaTeX Ghc-Options: -rtsopts -Wall -fno-warn-unused-do-bind @@ -1,4 +1,4 @@ -{-# LANGUAGE CPP #-} +{-# LANGUAGE CPP, TupleSections #-} {- Copyright (C) 2006-2014 John MacFarlane <jgm@berkeley.edu> @@ -33,16 +33,18 @@ module Main where import Text.Pandoc import Text.Pandoc.Builder (setMeta) import Text.Pandoc.PDF (makePDF) +import Text.Pandoc.Walk (walk) import Text.Pandoc.Readers.LaTeX (handleIncludes) import Text.Pandoc.Shared ( tabFilter, readDataFileUTF8, readDataFile, safeRead, headerShift, normalize, err, warn, openURL ) +import Text.Pandoc.MediaBag ( mediaDirectory, extractMediaBag, MediaBag ) import Text.Pandoc.XML ( toEntities ) import Text.Pandoc.SelfContained ( makeSelfContained ) import Text.Pandoc.Process (pipeProcess) import Text.Highlighting.Kate ( languages, Style, tango, pygments, espresso, zenburn, kate, haddock, monochrome ) -import System.Environment ( getArgs, getProgName ) +import System.Environment ( getArgs, getProgName, getEnvironment ) import System.Exit ( exitWith, ExitCode (..) ) import System.FilePath import System.Console.GetOpt @@ -55,7 +57,7 @@ import System.IO.Error ( isDoesNotExistError ) import qualified Control.Exception as E import Control.Exception.Extensible ( throwIO ) import qualified Text.Pandoc.UTF8 as UTF8 -import Control.Monad (when, unless, liftM) +import Control.Monad (when, unless, liftM, (>=>)) import Data.Foldable (foldrM) import Network.URI (parseURI, isURI, URI(..)) import qualified Data.ByteString.Lazy as B @@ -65,6 +67,11 @@ import qualified Data.Map as M import Data.Yaml (decode) import qualified Data.Yaml as Yaml import qualified Data.Text as T +import Control.Applicative ((<$>)) +import Text.Pandoc.Readers.Txt2Tags (getT2TMeta) +import Data.Monoid + +type Transform = Pandoc -> Pandoc copyrightMessage :: String copyrightMessage = "\nCopyright (C) 2006-2014 John MacFarlane\n" ++ @@ -96,7 +103,10 @@ isTextFormat s = takeWhile (`notElem` "+-") s `notElem` ["odt","docx","epub","ep externalFilter :: FilePath -> [String] -> Pandoc -> IO Pandoc externalFilter f args' d = do - mbexe <- if '/' `elem` f -- don't check PATH if filter name it has a path + mbPath <- lookup "PATH" <$> getEnvironment + mbexe <- if '/' `elem` f || mbPath == Nothing + -- don't check PATH if filter name has a path, or + -- if the PATH is not set then return Nothing else findExecutable f (f', args'') <- case mbexe of @@ -136,7 +146,7 @@ data Opt = Opt , optWriter :: String -- ^ Writer format , optParseRaw :: Bool -- ^ Parse unconvertable HTML and TeX , optTableOfContents :: Bool -- ^ Include table of contents - , optTransforms :: [Pandoc -> Pandoc] -- ^ Doc transforms to apply + , optTransforms :: [Transform] -- ^ Doc transforms to apply , optTemplate :: Maybe FilePath -- ^ Custom template , optVariables :: [(String,String)] -- ^ Template variables to set , optMetadata :: M.Map String MetaValue -- ^ Metadata fields to set @@ -179,8 +189,9 @@ data Opt = Opt , optAscii :: Bool -- ^ Use ascii characters only in html , optTeXLigatures :: Bool -- ^ Use TeX ligatures for quotes/dashes , optDefaultImageExtension :: String -- ^ Default image extension + , optExtractMedia :: Maybe FilePath -- ^ Path to extract embedded media , optTrace :: Bool -- ^ Print debug information - , optTrackChanges :: TrackChanges -- ^ Accept or reject MS Word track-changes. + , optTrackChanges :: TrackChanges -- ^ Accept or reject MS Word track-changes. } -- | Defaults for command-line options. @@ -236,6 +247,7 @@ defaultOpts = Opt , optAscii = False , optTeXLigatures = True , optDefaultImageExtension = "" + , optExtractMedia = Nothing , optTrace = False , optTrackChanges = AcceptChanges } @@ -340,6 +352,26 @@ options = "NUMBER") "" -- "Tab stop (default 4)" + , Option "" ["track-changes"] + (ReqArg + (\arg opt -> do + action <- case arg of + "accept" -> return AcceptChanges + "reject" -> return RejectChanges + "all" -> return AllChanges + _ -> err 6 + ("Unknown option for track-changes: " ++ arg) + return opt { optTrackChanges = action }) + "accept|reject|all") + "" -- "Accepting or reject MS Word track-changes."" + + , Option "" ["extract-media"] + (ReqArg + (\arg opt -> do + return opt { optExtractMedia = Just arg }) + "PATH") + "" -- "Directory to which to extract embedded media" + , Option "s" ["standalone"] (NoArg (\opt -> return opt { optStandalone = True })) @@ -784,19 +816,6 @@ options = (\opt -> return opt { optTrace = True })) "" -- "Turn on diagnostic tracing in readers." - , Option "" ["track-changes"] - (ReqArg - (\arg opt -> do - action <- case arg of - "accept" -> return AcceptChanges - "reject" -> return RejectChanges - "all" -> return AllChanges - _ -> err 6 - ("Unknown option for track-changes: " ++ arg) - return opt { optTrackChanges = action }) - "accept|reject|all") - "" -- "Accepting or reject MS Word track-changes."" - , Option "" ["dump-args"] (NoArg (\opt -> return opt { optDumpArgs = True })) @@ -876,6 +895,7 @@ defaultReaderName fallback (x:xs) = ".native" -> "native" ".json" -> "json" ".docx" -> "docx" + ".t2t" -> "t2t" _ -> defaultReaderName fallback xs -- Returns True if extension of first source is .lhs @@ -919,6 +939,31 @@ defaultWriterName x = ['.',y] | y `elem` ['1'..'9'] -> "man" _ -> "html" +-- Transformations of a Pandoc document post-parsing: + +extractMedia :: MediaBag -> FilePath -> Pandoc -> IO Pandoc +extractMedia media dir d = + case [fp | (fp, _, _) <- mediaDirectory media] of + [] -> return d + fps -> do + extractMediaBag True dir media + 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 _ _ x = x + +adjustMetadata :: M.Map String MetaValue -> Pandoc -> IO Pandoc +adjustMetadata metadata d = return $ M.foldWithKey setMeta d metadata + +applyTransforms :: [Transform] -> Pandoc -> IO Pandoc +applyTransforms transforms d = return $ foldr ($) d transforms + +applyFilters :: [FilePath] -> [String] -> Pandoc -> IO Pandoc +applyFilters filters args d = + foldrM ($) d $ map (flip externalFilter args) filters + main :: IO () main = do @@ -994,6 +1039,7 @@ main = do , optAscii = ascii , optTeXLigatures = texLigatures , optDefaultImageExtension = defaultImageExtension + , optExtractMedia = mbExtractMedia , optTrace = trace , optTrackChanges = trackChanges } = opts @@ -1010,7 +1056,6 @@ main = do all (\f -> takeBaseName f /= "pandoc-citeproc") filters -> "pandoc-citeproc" : filters _ -> filters - let plugins = map externalFilter filters' let sources = if ignoreArgs then [] else args @@ -1054,9 +1099,13 @@ main = do else e Right w -> return w - reader <- case getReader readerName' of - Right r -> return r - Left e -> err 7 e + reader <- if "t2t" == readerName' + then (mkStringReader . + readTxt2Tags) <$> + (getT2TMeta sources outputFile) + else case getReader readerName' of + Right r -> return r + Left e -> err 7 e let standalone' = standalone || not (isTextFormat writerName') || pdfOutput @@ -1099,6 +1148,7 @@ main = do $ lines dztempl return $ ("dzslides-core", dzcore) : variables' else return variables' + let sourceURL = case sources of [] -> Nothing (x:_) -> case parseURI x of @@ -1123,6 +1173,40 @@ main = do , readerTrackChanges = trackChanges } + when (not (isTextFormat writerName') && outputFile == "-") $ + err 5 $ "Cannot write " ++ writerName' ++ " output to stdout.\n" ++ + "Specify an output file using the -o option." + + let readSources [] = mapM readSource ["-"] + readSources srcs = mapM readSource srcs + readSource "-" = UTF8.getContents + readSource src = case parseURI src of + Just u | uriScheme u `elem` ["http:","https:"] -> + readURI src + _ -> UTF8.readFile src + readURI src = do + res <- openURL src + case res of + Left e -> throwIO e + Right (bs,_) -> return $ UTF8.toString bs + + let readFiles [] = error "Cannot read archive from stdin" + readFiles (x:_) = B.readFile x + + let convertTabs = tabFilter (if (preserveTabs || readerName' == "t2t") then 0 else tabStop) + + let handleIncludes' = if readerName' == "latex" || readerName' == "latex+lhs" + then handleIncludes + else return + + (doc, media) <- + case reader of + StringReader r-> (, mempty) <$> + ( readSources >=> + handleIncludes' . convertTabs . intercalate "\n" >=> + r readerOpts ) sources + ByteStringReader r -> readFiles sources >>= r readerOpts + let writerOptions = def { writerStandalone = standalone', writerTemplate = templ, writerVariables = variables'', @@ -1158,46 +1242,15 @@ main = do writerEpubChapterLevel = epubChapterLevel, writerTOCDepth = epubTOCDepth, writerReferenceODT = referenceODT, - writerReferenceDocx = referenceDocx + writerReferenceDocx = referenceDocx, + writerMediaBag = media } - when (not (isTextFormat writerName') && outputFile == "-") $ - err 5 $ "Cannot write " ++ writerName' ++ " output to stdout.\n" ++ - "Specify an output file using the -o option." - - let readSources [] = mapM readSource ["-"] - readSources srcs = mapM readSource srcs - readSource "-" = UTF8.getContents - readSource src = case parseURI src of - Just u | uriScheme u `elem` ["http:","https:"] -> - readURI src - _ -> UTF8.readFile src - readURI src = do - res <- openURL src - case res of - Left e -> throwIO e - Right (bs,_) -> return $ UTF8.toString bs - - let readFiles [] = error "Cannot read archive from stdin" - readFiles (x:_) = B.readFile x - - let convertTabs = tabFilter (if preserveTabs then 0 else tabStop) - - let handleIncludes' = if readerName' == "latex" || readerName' == "latex+lhs" - then handleIncludes - else return - - doc <- case reader of - StringReader r-> - readSources sources >>= - handleIncludes' . convertTabs . intercalate "\n" >>= - r readerOpts - ByteStringReader r -> readFiles sources >>= r readerOpts - - let doc0 = M.foldWithKey setMeta doc metadata - let doc1 = foldr ($) doc0 transforms - doc2 <- foldrM ($) doc1 $ map ($ [writerName']) plugins + doc' <- (maybe return (extractMedia media) mbExtractMedia >=> + adjustMetadata metadata >=> + applyTransforms transforms >=> + applyFilters filters' [writerName']) doc let writeBinary :: B.ByteString -> IO () writeBinary = B.writeFile (UTF8.encodePath outputFile) @@ -1207,8 +1260,8 @@ main = do writerFn f = UTF8.writeFile f case writer of - IOStringWriter f -> f writerOptions doc2 >>= writerFn outputFile - IOByteStringWriter f -> f writerOptions doc2 >>= writeBinary + IOStringWriter f -> f writerOptions doc' >>= writerFn outputFile + IOByteStringWriter f -> f writerOptions doc' >>= writeBinary PureStringWriter f | pdfOutput -> do -- make sure writer is latex or beamer @@ -1222,21 +1275,21 @@ main = do err 41 $ latexEngine ++ " not found. " ++ latexEngine ++ " is needed for pdf output." - res <- makePDF latexEngine f writerOptions doc2 + res <- makePDF latexEngine f writerOptions doc' case res of Right pdf -> writeBinary pdf Left err' -> do B.hPutStr stderr $ err' B.hPut stderr $ B.pack [10] err 43 "Error producing PDF from TeX source" - | otherwise -> selfcontain (f writerOptions doc2 ++ + | otherwise -> selfcontain (f writerOptions doc' ++ ['\n' | not standalone']) >>= writerFn outputFile . handleEntities where htmlFormat = writerName' `elem` ["html","html+lhs","html5","html5+lhs", "s5","slidy","slideous","dzslides","revealjs"] selfcontain = if selfContained && htmlFormat - then makeSelfContained datadir + then makeSelfContained writerOptions else return handleEntities = if htmlFormat && ascii then toEntities diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index b303fa7d7..77eb3e82f 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -63,6 +63,7 @@ module Text.Pandoc , writers -- * Readers: converting /to/ Pandoc format , Reader (..) + , mkStringReader , readDocx , readMarkdown , readMediaWiki @@ -76,6 +77,8 @@ module Text.Pandoc , readHaddock , readNative , readJSON + , readTxt2Tags + , readTxt2TagsNoMacros -- * Writers: converting /from/ Pandoc format , Writer (..) , writeNative @@ -130,6 +133,7 @@ import Text.Pandoc.Readers.Textile import Text.Pandoc.Readers.Native import Text.Pandoc.Readers.Haddock import Text.Pandoc.Readers.Docx +import Text.Pandoc.Readers.Txt2Tags import Text.Pandoc.Writers.Native import Text.Pandoc.Writers.Markdown import Text.Pandoc.Writers.RST @@ -157,6 +161,7 @@ import Text.Pandoc.Writers.Custom import Text.Pandoc.Templates import Text.Pandoc.Options import Text.Pandoc.Shared (safeRead, warn) +import Text.Pandoc.MediaBag (MediaBag) import Data.Aeson import qualified Data.ByteString.Lazy as BL import Data.List (intercalate) @@ -200,12 +205,12 @@ markdown o s = do return doc data Reader = StringReader (ReaderOptions -> String -> IO Pandoc) - | ByteStringReader (ReaderOptions -> BL.ByteString -> IO Pandoc) + | ByteStringReader (ReaderOptions -> BL.ByteString -> IO (Pandoc, MediaBag)) mkStringReader :: (ReaderOptions -> String -> Pandoc) -> Reader mkStringReader r = StringReader (\o s -> return $ r o s) -mkBSReader :: (ReaderOptions -> BL.ByteString -> Pandoc) -> Reader +mkBSReader :: (ReaderOptions -> BL.ByteString -> (Pandoc, MediaBag)) -> Reader mkBSReader r = ByteStringReader (\o s -> return $ r o s) -- | Association list of formats and readers. @@ -227,6 +232,7 @@ readers = [ ("native" , StringReader $ \_ s -> return $ readNative s) ,("latex" , mkStringReader readLaTeX) ,("haddock" , mkStringReader readHaddock) ,("docx" , mkBSReader readDocx) + ,("t2t" , mkStringReader readTxt2TagsNoMacros) ] data Writer = PureStringWriter (WriterOptions -> Pandoc -> String) diff --git a/src/Text/Pandoc/Compat/Directory.hs b/src/Text/Pandoc/Compat/Directory.hs new file mode 100644 index 000000000..61dd5c525 --- /dev/null +++ b/src/Text/Pandoc/Compat/Directory.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE CPP #-} +module Text.Pandoc.Compat.Directory ( getModificationTime ) + where + +#if MIN_VERSION_directory(1,2,0) +import System.Directory + + +#else +import qualified System.Directory as S +import Data.Time.Clock (UTCTime) +import Data.Time.Clock.POSIX +import System.Time + +getModificationTime :: FilePath -> IO UTCTime +getModificationTime fp = convert `fmap` S.getModificationTime fp + where + convert (TOD x _) = posixSecondsToUTCTime (realToFrac x) + +#endif + diff --git a/src/Text/Pandoc/MediaBag.hs b/src/Text/Pandoc/MediaBag.hs new file mode 100644 index 000000000..667089f55 --- /dev/null +++ b/src/Text/Pandoc/MediaBag.hs @@ -0,0 +1,107 @@ +{-# LANGUAGE GeneralizedNewtypeDeriving #-} +{- +Copyright (C) 2014 John MacFarlane <jgm@berkeley.edu> + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA +-} + +{- | + Module : Text.Pandoc.MediaBag + Copyright : Copyright (C) 2014 John MacFarlane + License : GNU GPL, version 2 or above + + Maintainer : John MacFarlane <jgm@berkeley.edu> + Stability : alpha + Portability : portable + +Definition of a MediaBag object to hold binary resources, and an +interface for interacting with it. +-} +module Text.Pandoc.MediaBag ( + MediaBag, + lookupMedia, + insertMedia, + mediaDirectory, + extractMediaBag + ) where +import System.FilePath +import System.Directory (createDirectoryIfMissing) +import qualified Data.Map as M +import qualified Data.ByteString.Lazy as BL +import Data.Monoid (Monoid) +import Control.Monad (when, MonadPlus(..)) +import Text.Pandoc.MIME (getMimeType) +import qualified Text.Pandoc.UTF8 as UTF8 +import Data.Maybe (fromMaybe) +import System.IO (stderr) + +-- | A container for a collection of binary resources, with names and +-- mime types. Note that a 'MediaBag' is a Monoid, so 'mempty' +-- can be used for an empty 'MediaBag', and '<>' can be used to append +-- two 'MediaBag's. +newtype MediaBag = MediaBag (M.Map String (String, BL.ByteString)) + deriving (Monoid) + +instance Show MediaBag where + show bag = "MediaBag " ++ show (mediaDirectory bag) + +-- | Insert a media item into a 'MediaBag', replacing any existing +-- value with the same name. +insertMedia :: FilePath -- ^ relative path and canonical name of resource + -> Maybe String -- ^ mime type (Nothing = determine from extension) + -> BL.ByteString -- ^ contents of resource + -> MediaBag + -> MediaBag +insertMedia fp mbMime contents (MediaBag mediamap) = + MediaBag (M.insert fp (mime, contents) mediamap) + where mime = fromMaybe "application/octet-stream" (mbMime `mplus` fallback) + fallback = case takeExtension fp of + ".gz" -> getMimeType $ dropExtension fp + _ -> getMimeType fp + +-- | Lookup a media item in a 'MediaBag', returning mime type and contents. +lookupMedia :: FilePath + -> MediaBag + -> Maybe (String, BL.ByteString) +lookupMedia fp (MediaBag mediamap) = M.lookup fp mediamap + +-- | Get a list of the file paths stored in a 'MediaBag', with +-- their corresponding mime types and the lengths in bytes of the contents. +mediaDirectory :: MediaBag -> [(String, String, Int)] +mediaDirectory (MediaBag mediamap) = + M.foldWithKey (\fp (mime,contents) -> + ((fp, mime, fromIntegral $ BL.length contents):)) [] mediamap + +-- | Extract contents of MediaBag to a given directory. Print informational +-- messages if 'verbose' is true. +extractMediaBag :: Bool + -> FilePath + -> MediaBag + -> IO () +extractMediaBag verbose dir (MediaBag mediamap) = do + sequence_ $ M.foldWithKey + (\fp (_ ,contents) -> + ((writeMedia verbose dir (fp, contents)):)) [] mediamap + +writeMedia :: Bool -> FilePath -> (FilePath, BL.ByteString) -> IO () +writeMedia verbose dir (subpath, bs) = do + -- we join and split to convert a/b/c to a\b\c on Windows; + -- in zip containers all paths use / + let fullpath = dir </> joinPath (splitPath subpath) + createDirectoryIfMissing True $ takeDirectory fullpath + when verbose $ UTF8.hPutStrLn stderr $ "pandoc: extracting " ++ fullpath + BL.writeFile fullpath bs + + diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index ac791ac74..85a6a3096 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -49,6 +49,8 @@ import Data.Set (Set) import qualified Data.Set as Set import Data.Default import Text.Pandoc.Highlighting (Style, pygments) +import Text.Pandoc.MediaBag (MediaBag) +import Data.Monoid -- | Individually selectable syntax extensions. data Extension = @@ -200,7 +202,6 @@ strictExtensions = Set.fromList data ReaderOptions = ReaderOptions{ readerExtensions :: Set Extension -- ^ Syntax extensions , readerSmart :: Bool -- ^ Smart punctuation - , readerStrict :: Bool -- ^ FOR TRANSITION ONLY , readerStandalone :: Bool -- ^ Standalone document with header , readerParseRaw :: Bool -- ^ Parse raw HTML, LaTeX , readerColumns :: Int -- ^ Number of columns in terminal @@ -220,7 +221,6 @@ instance Default ReaderOptions where def = ReaderOptions{ readerExtensions = pandocExtensions , readerSmart = False - , readerStrict = False , readerStandalone = False , readerParseRaw = False , readerColumns = 80 @@ -315,7 +315,8 @@ data WriterOptions = WriterOptions , writerEpubChapterLevel :: Int -- ^ Header level for chapters (separate files) , writerTOCDepth :: Int -- ^ Number of levels to include in TOC , writerReferenceODT :: Maybe FilePath -- ^ Path to reference ODT if specified - , writerReferenceDocx :: Maybe FilePath -- ^ Ptah to reference DOCX if specified + , writerReferenceDocx :: Maybe FilePath -- ^ Path to reference DOCX if specified + , writerMediaBag :: MediaBag -- ^ Media collected by docx or epub reader } deriving Show instance Default WriterOptions where @@ -358,6 +359,7 @@ instance Default WriterOptions where , writerTOCDepth = 3 , writerReferenceODT = Nothing , writerReferenceDocx = Nothing + , writerMediaBag = mempty } -- | Returns True if the given extension is enabled. diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index bd55c565f..35554637a 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -30,7 +30,6 @@ Conversion of LaTeX documents to PDF. -} module Text.Pandoc.PDF ( makePDF ) where -import System.IO.Temp import Data.ByteString.Lazy (ByteString) import qualified Data.ByteString.Lazy as B import qualified Data.ByteString.Lazy.Char8 as BC @@ -46,7 +45,7 @@ import Data.Maybe (fromMaybe) import qualified Text.Pandoc.UTF8 as UTF8 import Text.Pandoc.Definition import Text.Pandoc.Walk (walkM) -import Text.Pandoc.Shared (fetchItem, warn) +import Text.Pandoc.Shared (fetchItem', warn, withTempDir) import Text.Pandoc.Options (WriterOptions(..)) import Text.Pandoc.MIME (extensionFromMimeType) import Text.Pandoc.Process (pipeProcess) @@ -55,14 +54,6 @@ import qualified Data.ByteString.Lazy as BL import Data.List (intercalate) #endif -withTempDir :: String -> (FilePath -> IO a) -> IO a -withTempDir = -#ifdef _WINDOWS - withTempDirectory "." -#else - withSystemTempDirectory -#endif - #ifdef _WINDOWS changePathSeparators :: FilePath -> FilePath changePathSeparators = intercalate "/" . splitDirectories @@ -74,26 +65,26 @@ makePDF :: String -- ^ pdf creator (pdflatex, lualatex, xelatex) -> Pandoc -- ^ document -> IO (Either ByteString ByteString) makePDF program writer opts doc = withTempDir "tex2pdf." $ \tmpdir -> do - doc' <- handleImages (writerSourceURL opts) tmpdir doc + doc' <- handleImages opts tmpdir doc let source = writer opts doc' tex2pdf' tmpdir program source -handleImages :: Maybe String -- ^ source base URL +handleImages :: WriterOptions -> FilePath -- ^ temp dir to store images -> Pandoc -- ^ document -> IO Pandoc -handleImages baseURL tmpdir = walkM (handleImage' baseURL tmpdir) +handleImages opts tmpdir = walkM (handleImage' opts tmpdir) -handleImage' :: Maybe String +handleImage' :: WriterOptions -> FilePath -> Inline -> IO Inline -handleImage' baseURL tmpdir (Image ils (src,tit)) = do +handleImage' opts tmpdir (Image ils (src,tit)) = do exists <- doesFileExist src if exists then return $ Image ils (src,tit) else do - res <- fetchItem baseURL src + res <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src case res of Right (contents, Just mime) -> do let ext = fromMaybe (takeExtension src) $ diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index eec4a3bc9..b25fca100 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -2,6 +2,7 @@ FlexibleContexts , GeneralizedNewtypeDeriving , TypeSynonymInstances +, MultiParamTypeClasses , FlexibleInstances #-} {- Copyright (C) 2006-2014 John MacFarlane <jgm@berkeley.edu> @@ -80,6 +81,7 @@ module Text.Pandoc.Parsing ( anyLine, HeaderType (..), ParserContext (..), QuoteContext (..), + HasQuoteContext (..), NoteTable, NoteTable', KeyTable, @@ -88,7 +90,6 @@ module Text.Pandoc.Parsing ( anyLine, toKey, registerHeader, smartPunctuation, - withQuoteContext, singleQuoteStart, singleQuoteEnd, doubleQuoteStart, @@ -106,6 +107,7 @@ module Text.Pandoc.Parsing ( anyLine, runF, askF, asksF, + token, -- * Re-exports from Text.Pandoc.Parsec Stream, runParser, @@ -160,7 +162,6 @@ module Text.Pandoc.Parsing ( anyLine, setSourceColumn, setSourceLine, newPos, - token ) where @@ -170,7 +171,7 @@ import Text.Pandoc.Builder (Blocks, Inlines, rawBlock, HasMeta(..)) import qualified Text.Pandoc.Builder as B import Text.Pandoc.XML (fromEntities) import qualified Text.Pandoc.UTF8 as UTF8 (putStrLn) -import Text.Parsec +import Text.Parsec hiding (token) import Text.Parsec.Pos (newPos) import Data.Char ( toLower, toUpper, ord, chr, isAscii, isAlphaNum, isHexDigit, isSpace ) @@ -407,7 +408,7 @@ emailAddress = try $ toResult <$> mailbox <*> (char '@' *> domain) -- Schemes from http://www.iana.org/assignments/uri-schemes.html plus --- the unofficial schemes coap, doi, javascript. +-- the unofficial schemes coap, doi, javascript, isbn, pmid schemes :: [String] schemes = ["coap","doi","javascript","aaa","aaas","about","acap","cap","cid", "crid","data","dav","dict","dns","file","ftp","geo","go","gopher", @@ -429,7 +430,7 @@ schemes = ["coap","doi","javascript","aaa","aaas","about","acap","cap","cid", "rtmp","secondlife","sftp","sgn","skype","smb","soldat","spotify", "ssh","steam","svn","teamspeak","things","udp","unreal","ut2004", "ventrilo","view-source","webcal","wtai","wyciwyg","xfire","xri", - "ymsgr"] + "ymsgr", "isbn", "pmid"] uriScheme :: Stream s m Char => ParserT s st m String uriScheme = oneOfStringsCI schemes @@ -484,7 +485,8 @@ mathDisplayWith op cl = try $ do string op many1Till (noneOf "\n" <|> (newline <* notFollowedBy' blankline)) (try $ string cl) -mathDisplay :: Stream s m Char => ParserT s ParserState m String +mathDisplay :: (HasReaderOptions st, Stream s m Char) + => ParserT s st m String mathDisplay = (guardEnabled Ext_tex_math_dollars >> mathDisplayWith "$$" "$$") <|> (guardEnabled Ext_tex_math_single_backslash >> @@ -492,7 +494,8 @@ mathDisplay = <|> (guardEnabled Ext_tex_math_double_backslash >> mathDisplayWith "\\\\[" "\\\\]") -mathInline :: Stream s m Char => ParserT s ParserState m String +mathInline :: (HasReaderOptions st , Stream s m Char) + => ParserT s st m String mathInline = (guardEnabled Ext_tex_math_dollars >> mathInlineWith "$" "$") <|> (guardEnabled Ext_tex_math_single_backslash >> @@ -909,6 +912,21 @@ class HasReaderOptions st where -- default getOption f = (f . extractReaderOptions) <$> getState +class HasQuoteContext st m where + getQuoteContext :: (Stream s m t) => ParsecT s st m QuoteContext + withQuoteContext :: QuoteContext -> ParsecT s st m a -> ParsecT s st m a + +instance Monad m => HasQuoteContext ParserState m where + getQuoteContext = stateQuoteContext <$> getState + withQuoteContext context parser = do + oldState <- getState + let oldQuoteContext = stateQuoteContext oldState + setState oldState { stateQuoteContext = context } + result <- parser + newState <- getState + setState newState { stateQuoteContext = oldQuoteContext } + return result + instance HasReaderOptions ParserState where extractReaderOptions = stateOptions @@ -1051,9 +1069,9 @@ registerHeader (ident,classes,kvs) header' = do failUnlessSmart :: (Stream s m a, HasReaderOptions st) => ParserT s st m () failUnlessSmart = getOption readerSmart >>= guard -smartPunctuation :: Stream s m Char - => ParserT s ParserState m Inlines - -> ParserT s ParserState m Inlines +smartPunctuation :: (HasReaderOptions st, HasLastStrPosition st, HasQuoteContext st m, Stream s m Char) + => ParserT s st m Inlines + -> ParserT s st m Inlines smartPunctuation inlineParser = do failUnlessSmart choice [ quoted inlineParser, apostrophe, dash, ellipses ] @@ -1061,46 +1079,33 @@ smartPunctuation inlineParser = do apostrophe :: Stream s m Char => ParserT s st m Inlines apostrophe = (char '\'' <|> char '\8217') >> return (B.str "\x2019") -quoted :: Stream s m Char - => ParserT s ParserState m Inlines - -> ParserT s ParserState m Inlines +quoted :: (HasLastStrPosition st, HasQuoteContext st m, Stream s m Char) + => ParserT s st m Inlines + -> ParserT s st m Inlines quoted inlineParser = doubleQuoted inlineParser <|> singleQuoted inlineParser -withQuoteContext :: Stream s m t - => QuoteContext - -> ParserT s ParserState m a - -> ParserT s ParserState m a -withQuoteContext context parser = do - oldState <- getState - let oldQuoteContext = stateQuoteContext oldState - setState oldState { stateQuoteContext = context } - result <- parser - newState <- getState - setState newState { stateQuoteContext = oldQuoteContext } - return result - -singleQuoted :: Stream s m Char - => ParserT s ParserState m Inlines - -> ParserT s ParserState m Inlines +singleQuoted :: (HasLastStrPosition st, HasQuoteContext st m, Stream s m Char) + => ParserT s st m Inlines + -> ParserT s st m Inlines singleQuoted inlineParser = try $ do singleQuoteStart withQuoteContext InSingleQuote $ many1Till inlineParser singleQuoteEnd >>= return . B.singleQuoted . mconcat -doubleQuoted :: Stream s m Char - => ParserT s ParserState m Inlines - -> ParserT s ParserState m Inlines +doubleQuoted :: (HasQuoteContext st m, Stream s m Char) + => ParserT s st m Inlines + -> ParserT s st m Inlines doubleQuoted inlineParser = try $ do doubleQuoteStart withQuoteContext InDoubleQuote $ manyTill inlineParser doubleQuoteEnd >>= return . B.doubleQuoted . mconcat -failIfInQuoteContext :: Stream s m t +failIfInQuoteContext :: (HasQuoteContext st m, Stream s m t) => QuoteContext - -> ParserT s ParserState m () + -> ParserT s st m () failIfInQuoteContext context = do - st <- getState - if stateQuoteContext st == context + context' <- getQuoteContext + if context' == context then fail "already inside quotes" else return () @@ -1110,8 +1115,8 @@ charOrRef cs = guard (c `elem` cs) return c) -singleQuoteStart :: Stream s m Char - => ParserT s ParserState m () +singleQuoteStart :: (HasLastStrPosition st, HasQuoteContext st m, Stream s m Char) + => ParserT s st m () singleQuoteStart = do failIfInQuoteContext InSingleQuote -- single quote start can't be right after str @@ -1124,8 +1129,8 @@ singleQuoteEnd = try $ do charOrRef "'\8217\146" notFollowedBy alphaNum -doubleQuoteStart :: Stream s m Char - => ParserT s ParserState m () +doubleQuoteStart :: (HasQuoteContext st m, Stream s m Char) + => ParserT s st m () doubleQuoteStart = do failIfInQuoteContext InDoubleQuote try $ do charOrRef "\"\8220\147" @@ -1179,6 +1184,14 @@ citeKey = try $ do let key = firstChar:rest return (suppress_author, key) + +token :: (Stream s m t) + => (t -> String) + -> (t -> SourcePos) + -> (t -> Maybe a) + -> ParsecT s st m a +token pp pos match = tokenPrim pp (\_ t _ -> pos t) match + -- -- Macros -- @@ -1200,9 +1213,9 @@ macro = do else return $ rawBlock "latex" def' -- | Apply current macros to string. -applyMacros' :: Stream [Char] m Char +applyMacros' :: (HasReaderOptions st, HasMacros st, Stream [Char] m Char) => String - -> ParserT [Char] ParserState m String + -> ParserT [Char] st m String applyMacros' target = do apply <- getOption readerApplyMacros if apply diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs index d25ba725f..1e72c2040 100644 --- a/src/Text/Pandoc/Pretty.hs +++ b/src/Text/Pandoc/Pretty.hs @@ -35,6 +35,7 @@ module Text.Pandoc.Pretty ( , render , cr , blankline + , blanklines , space , text , char @@ -100,7 +101,7 @@ data D = Text Int String | BreakingSpace | CarriageReturn | NewLine - | BlankLine + | BlankLines Int -- number of blank lines deriving (Show) newtype Doc = Doc { unDoc :: Seq D } @@ -113,7 +114,7 @@ isBlank :: D -> Bool isBlank BreakingSpace = True isBlank CarriageReturn = True isBlank NewLine = True -isBlank BlankLine = True +isBlank (BlankLines _) = True isBlank (Text _ (c:_)) = isSpace c isBlank _ = False @@ -190,7 +191,7 @@ vsep = foldr ($+$) empty nestle :: Doc -> Doc nestle (Doc d) = Doc $ go d where go x = case viewl x of - (BlankLine :< rest) -> go rest + (BlankLines _ :< rest) -> go rest (NewLine :< rest) -> go rest _ -> x @@ -203,7 +204,7 @@ chomp d = Doc (fromList dl') go (BreakingSpace : xs) = go xs go (CarriageReturn : xs) = go xs go (NewLine : xs) = go xs - go (BlankLine : xs) = go xs + go (BlankLines _ : xs) = go xs go (Prefixed s d' : xs) = Prefixed s (chomp d') : xs go xs = xs @@ -216,9 +217,10 @@ outp off s | off < 0 = do -- offset < 0 means newline characters let pref = reverse $ dropWhile isSpace $ reverse rawpref modify $ \st -> st{ output = fromString pref : output st , column = column st + realLength pref } + let numnewlines = length $ takeWhile (=='\n') $ reverse s modify $ \st -> st { output = fromString s : output st , column = 0 - , newlines = newlines st + 1 } + , newlines = newlines st + numnewlines } outp off s = do -- offset >= 0 (0 might be combining char) st' <- get let pref = prefix st' @@ -277,15 +279,11 @@ renderList (BeforeNonBlank d : xs) = | otherwise -> renderDoc d >> renderList xs [] -> renderList xs -renderList (BlankLine : xs) = do +renderList (BlankLines num : xs) = do st <- get case output st of - _ | newlines st > 1 || null xs -> return () - _ | column st == 0 -> do - outp (-1) "\n" - _ -> do - outp (-1) "\n" - outp (-1) "\n" + _ | newlines st > num || null xs -> return () + | otherwise -> replicateM_ (1 + num - newlines st) (outp (-1) "\n") renderList xs renderList (CarriageReturn : xs) = do @@ -302,7 +300,7 @@ renderList (NewLine : xs) = do renderList (BreakingSpace : CarriageReturn : xs) = renderList (CarriageReturn:xs) renderList (BreakingSpace : NewLine : xs) = renderList (NewLine:xs) -renderList (BreakingSpace : BlankLine : xs) = renderList (BlankLine:xs) +renderList (BreakingSpace : BlankLines n : xs) = renderList (BlankLines n:xs) renderList (BreakingSpace : BreakingSpace : xs) = renderList (BreakingSpace:xs) renderList (BreakingSpace : xs) = do let isText (Text _ _) = True @@ -383,9 +381,13 @@ cr = Doc $ singleton CarriageReturn -- | Inserts a blank line unless one exists already. -- (@blankline <> blankline@ has the same effect as @blankline@. --- If you want multiple blank lines, use @text "\\n\\n"@. blankline :: Doc -blankline = Doc $ singleton BlankLine +blankline = Doc $ singleton (BlankLines 1) + +-- | Inserts a blank lines unless they exists already. +-- (@blanklines m <> blanklines n@ has the same effect as @blankline (max m n)@. +blanklines :: Int -> Doc +blanklines n = Doc $ singleton (BlankLines n) -- | Uses the specified string as a prefix for every line of -- the inside document (except the first, if not at the beginning diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index 196a3cec5..86ce62ced 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -78,19 +78,17 @@ import Codec.Archive.Zip import Text.Pandoc.Definition import Text.Pandoc.Options import Text.Pandoc.Builder (text, toList) -import Text.Pandoc.MIME (getMimeType) -import Text.Pandoc.UTF8 (toString) import Text.Pandoc.Walk import Text.Pandoc.Readers.Docx.Parse import Text.Pandoc.Readers.Docx.Lists import Text.Pandoc.Readers.Docx.Reducible import Text.Pandoc.Readers.Docx.TexChar import Text.Pandoc.Shared +import Text.Pandoc.MediaBag (insertMedia, MediaBag) import Data.Maybe (mapMaybe, fromMaybe) -import Data.List (delete, isPrefixOf, (\\), intercalate) -import qualified Data.ByteString as BS +import Data.List (delete, isPrefixOf, (\\), intercalate, intersect) +import Data.Monoid import qualified Data.ByteString.Lazy as B -import Data.ByteString.Base64 (encode) import qualified Data.Map as M import Control.Monad.Reader import Control.Monad.State @@ -98,16 +96,24 @@ import Text.Printf (printf) readDocx :: ReaderOptions -> B.ByteString - -> Pandoc + -> (Pandoc, MediaBag) readDocx opts bytes = case archiveToDocx (toArchive bytes) of - Right docx -> Pandoc nullMeta (docxToBlocks opts docx) + Right docx -> (Pandoc meta blks, mediaBag) where + (meta, blks, mediaBag) = (docxToOutput opts docx) Left _ -> error $ "couldn't parse docx file" data DState = DState { docxAnchorMap :: M.Map String String + , docxMediaBag :: MediaBag , docxInHeaderBlock :: Bool , docxInTexSubscript :: Bool } +defaultDState :: DState +defaultDState = DState { docxAnchorMap = M.empty + , docxMediaBag = mempty + , docxInHeaderBlock = False + , docxInTexSubscript = False} + data DEnv = DEnv { docxOptions :: ReaderOptions , docxDocument :: Docx} @@ -134,6 +140,65 @@ spansToKeep = [] divsToKeep :: [String] divsToKeep = ["list-item", "Definition", "DefinitionTerm"] +metaStyles :: M.Map String String +metaStyles = M.fromList [ ("Title", "title") + , ("Subtitle", "subtitle") + , ("Author", "author") + , ("Date", "date") + , ("Abstract", "abstract")] + +sepBodyParts :: [BodyPart] -> ([BodyPart], [BodyPart]) +sepBodyParts = span (\bp -> (isMetaPar bp || isEmptyPar bp)) + +isMetaPar :: BodyPart -> Bool +isMetaPar (Paragraph pPr _) = + not $ null $ intersect (pStyle pPr) (M.keys metaStyles) +isMetaPar _ = False + +isEmptyPar :: BodyPart -> Bool +isEmptyPar (Paragraph _ parParts) = + all isEmptyParPart parParts + where + isEmptyParPart (PlainRun (Run _ runElems)) = all isEmptyElem runElems + isEmptyParPart _ = False + isEmptyElem (TextRun s) = trim s == "" + isEmptyElem _ = True +isEmptyPar _ = False + +bodyPartsToMeta' :: [BodyPart] -> DocxContext (M.Map String MetaValue) +bodyPartsToMeta' [] = return M.empty +bodyPartsToMeta' (bp : bps) + | (Paragraph pPr parParts) <- bp + , (c : _)<- intersect (pStyle pPr) (M.keys metaStyles) + , (Just metaField) <- M.lookup c metaStyles = do + inlines <- parPartsToInlines parParts + remaining <- bodyPartsToMeta' bps + let + f (MetaInlines ils) (MetaInlines ils') = MetaBlocks [Para ils, Para ils'] + f (MetaInlines ils) (MetaBlocks blks) = MetaBlocks ((Para ils) : blks) + f m (MetaList mv) = MetaList (m : mv) + f m n = MetaList [m, n] + return $ M.insertWith f metaField (MetaInlines inlines) remaining +bodyPartsToMeta' (_ : bps) = bodyPartsToMeta' bps + +bodyPartsToMeta :: [BodyPart] -> DocxContext Meta +bodyPartsToMeta bps = do + mp <- bodyPartsToMeta' bps + let mp' = + case M.lookup "author" mp of + Just mv -> M.insert "author" (fixAuthors mv) mp + Nothing -> mp + return $ Meta mp' + +fixAuthors :: MetaValue -> MetaValue +fixAuthors (MetaBlocks blks) = + MetaList $ map g $ filter f blks + where f (Para _) = True + f _ = False + g (Para ils) = MetaInlines ils + g _ = MetaInlines [] +fixAuthors mv = mv + runStyleToContainers :: RunStyle -> [Container Inline] runStyleToContainers rPr = let spanClassToContainers :: String -> [Container Inline] @@ -154,7 +219,8 @@ runStyleToContainers rPr = , if isStrike rPr then (Just Strikeout) else Nothing , if isSuperScript rPr then (Just Superscript) else Nothing , if isSubScript rPr then (Just Subscript) else Nothing - , rUnderline rPr >>= (\f -> Just $ Span ("", [], [("underline", f)])) + , rUnderline rPr >>= + (\f -> if f == "single" then (Just Emph) else Nothing) ] in classContainers ++ formatters @@ -259,13 +325,6 @@ runToInlines (Footnote bps) = runToInlines (Endnote bps) = concatMapM bodyPartToBlocks bps >>= (\blks -> return [Note blks]) -makeDataUrl :: String -> B.ByteString -> Maybe String -makeDataUrl fp bs = - case getMimeType fp of - Just mime -> Just $ "data:" ++ mime ++ ";base64," ++ - toString (encode $ BS.concat $ B.toChunks bs) - Nothing -> Nothing - parPartToInlines :: ParPart -> DocxContext [Inline] parPartToInlines (PlainRun r) = runToInlines r parPartToInlines (Insertion _ author date runs) = do @@ -312,11 +371,9 @@ parPartToInlines (BookMark _ anchor) = modify $ \s -> s { docxAnchorMap = M.insert anchor newAnchor anchorMap} return [Span (newAnchor, ["anchor"], []) []] parPartToInlines (Drawing fp bs) = do - return $ case True of -- TODO: add self-contained images - True -> [Image [] (fp, "")] - False -> case makeDataUrl fp bs of - Just d -> [Image [] (d, "")] - Nothing -> [Image [] ("", "")] + mediaBag <- gets docxMediaBag + modify $ \s -> s { docxMediaBag = insertMedia fp Nothing bs mediaBag } + return [Image [] (fp, "")] parPartToInlines (InternalHyperLink anchor runs) = do ils <- concatMapM runToInlines runs return [Link ils ('#' : anchor, "")] @@ -615,24 +672,25 @@ rewriteLink l@(Link ils ('#':target, title)) = do Nothing -> l rewriteLink il = return il - -bodyToBlocks :: Body -> DocxContext [Block] -bodyToBlocks (Body bps) = do - blks <- concatMapM bodyPartToBlocks bps >>= +bodyToOutput :: Body -> DocxContext (Meta, [Block], MediaBag) +bodyToOutput (Body bps) = do + let (metabps, blkbps) = sepBodyParts bps + meta <- bodyPartsToMeta metabps + blks <- concatMapM bodyPartToBlocks blkbps >>= walkM rewriteLink - return $ - blocksToDefinitions $ - blocksToBullets $ blks - -docxToBlocks :: ReaderOptions -> Docx -> [Block] -docxToBlocks opts d@(Docx (Document _ body)) = - let dState = DState { docxAnchorMap = M.empty - , docxInHeaderBlock = False - , docxInTexSubscript = False} + mediaBag <- gets docxMediaBag + return $ (meta, + blocksToDefinitions $ blocksToBullets $ blks, + mediaBag) + +docxToOutput :: ReaderOptions -> Docx -> (Meta, [Block], MediaBag) +docxToOutput opts d@(Docx (Document _ body)) = + let dState = defaultDState dEnv = DEnv { docxOptions = opts , docxDocument = d} in - evalDocxContext (bodyToBlocks body) dEnv dState + evalDocxContext (bodyToOutput body) dEnv dState + ilToCode :: Inline -> String ilToCode (Str s) = s diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index 8541a1a3a..71938afe0 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -779,11 +779,11 @@ expandDrawingId :: String -> D ParPart expandDrawingId s = do target <- asks (lookupRelationship s . envRelationships) case target of - Just t -> do let filepath = combine "word" t - bytes <- asks (lookup filepath . envMedia) - case bytes of - Just bs -> return $ Drawing filepath bs - Nothing -> throwError DocxError + Just filepath -> do + bytes <- asks (lookup (combine "word" filepath) . envMedia) + case bytes of + Just bs -> return $ Drawing filepath bs + Nothing -> throwError DocxError Nothing -> throwError DocxError elemToParPart :: NameSpaces -> Element -> D ParPart diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 2414dfbf7..597156a5e 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -1,3 +1,4 @@ +{-# LANGUAGE FlexibleContexts, FlexibleInstances, MultiParamTypeClasses #-} {- Copyright (C) 2006-2014 John MacFarlane <jgm@berkeley.edu> @@ -40,7 +41,7 @@ import Text.HTML.TagSoup import Text.HTML.TagSoup.Match import Text.Pandoc.Definition import qualified Text.Pandoc.Builder as B -import Text.Pandoc.Builder (Blocks, Inlines, trimInlines) +import Text.Pandoc.Builder (HasMeta (..), Blocks, Inlines, trimInlines) import Text.Pandoc.Shared import Text.Pandoc.Options import Text.Pandoc.Parsing @@ -52,6 +53,8 @@ import Control.Applicative ( (<$>), (<$), (<*) ) import Data.Monoid import Text.Printf (printf) import Debug.Trace (trace) +import Data.Default (Default (..)) +import Control.Monad.Reader (Reader, runReader, asks, local, ask) isSpace :: Char -> Bool isSpace ' ' = True @@ -64,17 +67,26 @@ readHtml :: ReaderOptions -- ^ Reader options -> String -- ^ String to parse (assumes @'\n'@ line endings) -> Pandoc readHtml opts inp = - case runParser parseDoc def{ stateOptions = opts } "source" tags of + case flip runReader def $ runParserT parseDoc (HTMLState def{ stateOptions = opts } ) "source" tags of Left err' -> error $ "\nError at " ++ show err' Right result -> result where tags = canonicalizeTags $ parseTagsOptions parseOptions{ optTagPosition = True } inp parseDoc = do blocks <- (fixPlains False) . mconcat <$> manyTill block eof - meta <- stateMeta <$> getState + meta <- stateMeta . parserState <$> getState return $ Pandoc meta (B.toList blocks) -type TagParser = Parser [Tag String] ParserState +data HTMLState = + HTMLState + { parserState :: ParserState + } + +data HTMLLocal = HTMLLocal { quoteContext :: QuoteContext } + +type HTMLParser s = ParserT s HTMLState (Reader HTMLLocal) + +type TagParser = HTMLParser [Tag String] pBody :: TagParser Blocks pBody = pInTags "body" block @@ -115,7 +127,6 @@ block = do (take 60 $ show $ B.toList res)) (return ()) return res - pList :: TagParser Blocks pList = pBulletList <|> pOrderedList <|> pDefinitionList @@ -365,8 +376,8 @@ pSelfClosing f g = do pQ :: TagParser Inlines pQ = do - quoteContext <- stateQuoteContext `fmap` getState - let quoteType = case quoteContext of + context <- asks quoteContext + let quoteType = case context of InDoubleQuote -> SingleQuote _ -> DoubleQuote let innerQuoteContext = if quoteType == SingleQuote @@ -477,7 +488,8 @@ pTagText :: TagParser Inlines pTagText = try $ do (TagText str) <- pSatisfy isTagText st <- getState - case runParser (many pTagContents) st "text" str of + qu <- ask + case flip runReader qu $ runParserT (many pTagContents) st "text" str of Left _ -> fail $ "Could not parse `" ++ str ++ "'" Right result -> return $ mconcat result @@ -486,7 +498,9 @@ pBlank = try $ do (TagText str) <- pSatisfy isTagText guard $ all isSpace str -pTagContents :: Parser [Char] ParserState Inlines +type InlinesParser = HTMLParser String + +pTagContents :: InlinesParser Inlines pTagContents = B.displayMath <$> mathDisplay <|> B.math <$> mathInline @@ -496,12 +510,11 @@ pTagContents = <|> pSymbol <|> pBad -pStr :: Parser [Char] ParserState Inlines +pStr :: InlinesParser Inlines pStr = do result <- many1 $ satisfy $ \c -> not (isSpace c) && not (isSpecial c) && not (isBad c) - pos <- getPosition - updateState $ \s -> s{ stateLastStrPos = Just pos } + updateLastStrPos return $ B.str result isSpecial :: Char -> Bool @@ -516,13 +529,13 @@ isSpecial '\8220' = True isSpecial '\8221' = True isSpecial _ = False -pSymbol :: Parser [Char] ParserState Inlines +pSymbol :: InlinesParser Inlines pSymbol = satisfy isSpecial >>= return . B.str . (:[]) isBad :: Char -> Bool isBad c = c >= '\128' && c <= '\159' -- not allowed in HTML -pBad :: Parser [Char] ParserState Inlines +pBad :: InlinesParser Inlines pBad = do c <- satisfy isBad let c' = case c of @@ -556,7 +569,7 @@ pBad = do _ -> '?' return $ B.str [c'] -pSpace :: Parser [Char] ParserState Inlines +pSpace :: InlinesParser Inlines pSpace = many1 (satisfy isSpace) >> return B.space -- @@ -672,19 +685,23 @@ _ `closes` _ = False --- parsers for use in markdown, textile readers -- | Matches a stretch of HTML in balanced tags. -htmlInBalanced :: (Tag String -> Bool) -> Parser [Char] ParserState String +htmlInBalanced :: (Monad m) + => (Tag String -> Bool) + -> ParserT String st m String htmlInBalanced f = try $ do (TagOpen t _, tag) <- htmlTag f guard $ '/' `notElem` tag -- not a self-closing tag let stopper = htmlTag (~== TagClose t) - let anytag = liftM snd $ htmlTag (const True) + let anytag = snd <$> htmlTag (const True) contents <- many $ notFollowedBy' stopper >> (htmlInBalanced f <|> anytag <|> count 1 anyChar) endtag <- liftM snd stopper return $ tag ++ concat contents ++ endtag -- | Matches a tag meeting a certain condition. -htmlTag :: (Tag String -> Bool) -> Parser [Char] st (Tag String, String) +htmlTag :: Monad m + => (Tag String -> Bool) + -> ParserT [Char] st m (Tag String, String) htmlTag f = try $ do lookAhead $ char '<' >> (oneOf "/!?" <|> letter) (next : _) <- getInput >>= return . canonicalizeTags . parseTags @@ -707,3 +724,29 @@ mkAttr attr = (attribsId, attribsClasses, attribsKV) attribsKV = filter (\(k,_) -> k /= "class" && k /= "id") attr +-- Instances + +-- This signature should be more general +-- MonadReader HTMLLocal m => HasQuoteContext st m +instance HasQuoteContext st (Reader HTMLLocal) where + getQuoteContext = asks quoteContext + withQuoteContext q = local (\s -> s{quoteContext = q}) + +instance HasReaderOptions HTMLState where + extractReaderOptions = extractReaderOptions . parserState + +instance Default HTMLState where + def = HTMLState def + +instance HasMeta HTMLState where + setMeta s b st = st {parserState = setMeta s b $ parserState st} + deleteMeta s st = st {parserState = deleteMeta s $ parserState st} + +instance Default HTMLLocal where + def = HTMLLocal NoQuote + +instance HasLastStrPosition HTMLState where + setLastStrPos s st = st {parserState = setLastStrPos s (parserState st)} + getLastStrPos = getLastStrPos . parserState + + diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs new file mode 100644 index 000000000..3a51b9d84 --- /dev/null +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -0,0 +1,548 @@ +{-# LANGUAGE ViewPatterns #-} +{- +Copyright (C) 2014 Matthew Pickering <matthewtpickering@gmail.com> + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA +-} + +{- | + Module : Text.Pandoc.Readers.Txt2Tags + Copyright : Copyright (C) 2014 Matthew Pickering + License : GNU GPL, version 2 or above + + Maintainer : Matthew Pickering <matthewtpickering@gmail.com> + +Conversion of txt2tags formatted plain text to 'Pandoc' document. +-} +module Text.Pandoc.Readers.Txt2Tags ( readTxt2Tags + , getT2TMeta + , T2TMeta (..) + , readTxt2TagsNoMacros) + where + +import qualified Text.Pandoc.Builder as B +import Text.Pandoc.Builder ( Inlines, Blocks, (<>) + , trimInlines ) +import Text.Pandoc.Definition +import Text.Pandoc.Options +import Text.Pandoc.Shared (escapeURI,compactify', compactify'DL) +import Text.Pandoc.Parsing hiding (space, spaces, uri, macro) +import Control.Applicative ((<$>), (<$), (<*>), (<*), (*>)) +import Data.Char (toLower) +import Data.List (transpose, intersperse, intercalate) +import Data.Maybe (fromMaybe) +import Data.Monoid (Monoid, mconcat, mempty, mappend) +--import Network.URI (isURI) -- Not sure whether to use this function +import Control.Monad (void, guard, when) +import Data.Default +import Control.Monad.Reader (Reader, runReader, asks) + +import Data.Time.LocalTime (getZonedTime) +import Text.Pandoc.Compat.Directory(getModificationTime) +import Data.Time.Format (formatTime) +import System.Locale (defaultTimeLocale) +import System.IO.Error (catchIOError) + +type T2T = ParserT String ParserState (Reader T2TMeta) + +-- | An object for the T2T macros meta information +-- the contents of each field is simply substituted verbatim into the file +data T2TMeta = T2TMeta { + date :: String -- ^ Current date + , mtime :: String -- ^ Last modification time of infile + , infile :: FilePath -- ^ Input file + , outfile :: FilePath -- ^ Output file + } deriving Show + +instance Default T2TMeta where + def = T2TMeta "" "" "" "" + +-- | Get the meta information required by Txt2Tags macros +getT2TMeta :: [FilePath] -> FilePath -> IO T2TMeta +getT2TMeta inps out = do + curDate <- formatTime defaultTimeLocale "%F" <$> getZonedTime + let getModTime = fmap (formatTime defaultTimeLocale "%F") . + getModificationTime + curMtime <- catchIOError + (maximum <$> mapM getModTime inps) + (const (return "")) + return $ T2TMeta curDate curMtime (intercalate ", " inps) out + +-- | Read Txt2Tags from an input string returning a Pandoc document +readTxt2Tags :: T2TMeta -> ReaderOptions -> String -> Pandoc +readTxt2Tags t opts s = flip runReader t $ readWithM parseT2T (def {stateOptions = opts}) (s ++ "\n\n") + +-- | Read Txt2Tags (ignoring all macros) from an input string returning +-- a Pandoc document +readTxt2TagsNoMacros :: ReaderOptions -> String -> Pandoc +readTxt2TagsNoMacros = readTxt2Tags def + +parseT2T :: T2T Pandoc +parseT2T = do + _ <- (Nothing <$ try blankline) <|> (Just <$> (count 3 anyLine)) + config <- manyTill setting (notFollowedBy setting) + -- TODO: Handle settings better + let settings = foldr (\(k,v) -> B.setMeta k (MetaString v)) nullMeta config + updateState (\s -> s {stateMeta = settings}) + body <- mconcat <$> manyTill block eof + return $ Pandoc mempty (B.toList body) + +type Keyword = String +type Value = String + +setting :: T2T (Keyword, Value) +setting = do + string "%!" + keyword <- ignoreSpacesCap (many1 alphaNum) + char ':' + value <- ignoreSpacesCap (manyTill anyChar (newline)) + return (keyword, value) + +-- Blocks + +parseBlocks :: T2T Blocks +parseBlocks = mconcat <$> manyTill block eof + +block :: T2T Blocks +block = do + choice + [ mempty <$ blanklines + , quote + , hrule -- hrule must go above title + , title + , commentBlock + , verbatim + , rawBlock + , taggedBlock + , list + , table + , para + ] + +title :: T2T Blocks +title = try $ balancedTitle '+' <|> balancedTitle '=' + +balancedTitle :: Char -> T2T Blocks +balancedTitle c = try $ do + spaces + level <- length <$> many1 (char c) + guard (level <= 5) -- Max header level 5 + heading <- manyTill (noneOf "\n\r") (count level (char c)) + label <- optionMaybe (enclosed (char '[') (char ']') (alphaNum <|> oneOf "_-")) + many spaceChar *> newline + let attr = maybe nullAttr (\x -> (x, [], [])) label + return $ B.headerWith attr level (trimInlines $ B.text heading) + +para :: T2T Blocks +para = try $ do + ils <- parseInlines + nl <- option False (True <$ newline) + option (B.plain ils) (guard nl >> notFollowedBy listStart >> return (B.para ils)) + where + listStart = try bulletListStart <|> orderedListStart + +commentBlock :: T2T Blocks +commentBlock = try (blockMarkupArea (anyLine) (const mempty) "%%%") <|> comment + +-- Seperator and Strong line treated the same +hrule :: T2T Blocks +hrule = try $ do + spaces + line <- many1 (oneOf "=-_") + guard (length line >= 20) + B.horizontalRule <$ blankline + +quote :: T2T Blocks +quote = try $ do + lookAhead tab + rawQuote <- many1 (tab *> optional spaces *> anyLine) + contents <- parseFromString parseBlocks (intercalate "\n" rawQuote ++ "\n\n") + return $ B.blockQuote contents + +commentLine :: T2T Inlines +commentLine = comment + +-- List Parsing code from Org Reader + +list :: T2T Blocks +list = choice [bulletList, orderedList, definitionList] + +bulletList :: T2T Blocks +bulletList = B.bulletList . compactify' + <$> many1 (listItem bulletListStart parseBlocks) + +orderedList :: T2T Blocks +orderedList = B.orderedList . compactify' + <$> many1 (listItem orderedListStart parseBlocks) + +definitionList :: T2T Blocks +definitionList = try $ do + B.definitionList . compactify'DL <$> + many1 (listItem definitionListStart definitionListEnd) + +definitionListEnd :: T2T (Inlines, [Blocks]) +definitionListEnd = (,) <$> (mconcat <$> manyTill inline newline) <*> ((:[]) <$> parseBlocks) + +genericListStart :: T2T Char + -> T2T Int +genericListStart listMarker = try $ + (2+) <$> (length <$> many spaceChar + <* listMarker <* space <* notFollowedBy space) + +-- parses bullet list \start and returns its length (excl. following whitespace) +bulletListStart :: T2T Int +bulletListStart = genericListStart (char '-') + +orderedListStart :: T2T Int +orderedListStart = genericListStart (char '+' ) + +definitionListStart :: T2T Int +definitionListStart = genericListStart (char ':') + +-- parse raw text for one list item, excluding start marker and continuations +listItem :: T2T Int + -> T2T a + -> T2T a +listItem start end = try $ do + markerLength <- try start + firstLine <- anyLineNewline + blank <- option "" ("\n" <$ blankline) + rest <- concat <$> many (listContinuation markerLength) + parseFromString end $ firstLine ++ blank ++ rest + +-- continuation of a list item - indented and separated by blankline or endline. +-- Note: nested lists are parsed as continuations. +listContinuation :: Int + -> T2T String +listContinuation markerLength = try $ + notFollowedBy' (blankline >> blankline) + *> (mappend <$> (concat <$> many1 listLine) + <*> many blankline) + where listLine = try $ indentWith markerLength *> anyLineNewline + +anyLineNewline :: T2T String +anyLineNewline = (++ "\n") <$> anyLine + +indentWith :: Int -> T2T String +indentWith n = count n space + +-- Table + +table :: T2T Blocks +table = try $ do + header <- fmap snd <$> option mempty (try headerRow) + rows <- many1 (many commentLine *> tableRow) + let columns = transpose rows + let ncolumns = length columns + let aligns = map (foldr1 findAlign) (map (map fst) columns) + let rows' = map (map snd) rows + let size = maximum (map length rows') + let rowsPadded = map (pad size) rows' + let headerPadded = if (not (null header)) then pad size header else mempty + return $ B.table mempty + (zip aligns (replicate ncolumns 0.0)) + headerPadded rowsPadded + +pad :: (Show a, Monoid a) => Int -> [a] -> [a] +pad n xs = xs ++ (replicate (n - length xs) mempty) + + +findAlign :: Alignment -> Alignment -> Alignment +findAlign x y + | x == y = x + | otherwise = AlignDefault + +headerRow :: T2T [(Alignment, Blocks)] +headerRow = genericRow (string "||") + +tableRow :: T2T [(Alignment, Blocks)] +tableRow = genericRow (char '|') + +genericRow :: T2T a -> T2T [(Alignment, Blocks)] +genericRow start = try $ do + spaces *> start + manyTill tableCell newline <?> "genericRow" + + +tableCell :: T2T (Alignment, Blocks) +tableCell = try $ do + leftSpaces <- length <$> lookAhead (many1 space) -- Case of empty cell means we must lookAhead + content <- (manyTill inline (try $ lookAhead (cellEnd))) + rightSpaces <- length <$> many space + let align = + case compare leftSpaces rightSpaces of + LT -> AlignLeft + EQ -> AlignCenter + GT -> AlignRight + endOfCell + return $ (align, B.plain (B.trimInlines $ mconcat content)) + where + cellEnd = (void newline <|> (many1 space *> endOfCell)) + +endOfCell :: T2T () +endOfCell = try (skipMany1 $ char '|') <|> ( () <$ lookAhead newline) + +-- Raw area + +verbatim :: T2T Blocks +verbatim = genericBlock anyLineNewline B.codeBlock "```" + +rawBlock :: T2T Blocks +rawBlock = genericBlock anyLineNewline (B.para . B.str) "\"\"\"" + +taggedBlock :: T2T Blocks +taggedBlock = do + target <- getTarget + genericBlock anyLineNewline (B.rawBlock target) "'''" + +-- Generic + +genericBlock :: Monoid a => T2T a -> (a -> Blocks) -> String -> T2T Blocks +genericBlock p f s = blockMarkupArea p f s <|> blockMarkupLine p f s + +blockMarkupArea :: Monoid a => (T2T a) -> (a -> Blocks) -> String -> T2T Blocks +blockMarkupArea p f s = try $ (do + string s *> blankline + f . mconcat <$> (manyTill p (eof <|> void (string s *> blankline)))) + +blockMarkupLine :: T2T a -> (a -> Blocks) -> String -> T2T Blocks +blockMarkupLine p f s = try (f <$> (string s *> space *> p)) + +-- Can be in either block or inline position +comment :: Monoid a => T2T a +comment = try $ do + atStart + notFollowedBy macro + mempty <$ (char '%' *> anyLine) + +-- Inline + +parseInlines :: T2T Inlines +parseInlines = trimInlines . mconcat <$> many1 inline + +inline :: T2T Inlines +inline = do + choice + [ endline + , macro + , commentLine + , whitespace + , url + , link + , image + , bold + , underline + , code + , raw + , tagged + , strike + , italic + , code + , str + , symbol + ] + +bold :: T2T Inlines +bold = inlineMarkup inline B.strong '*' (B.str) + +underline :: T2T Inlines +underline = inlineMarkup inline B.emph '_' (B.str) + +strike :: T2T Inlines +strike = inlineMarkup inline B.strikeout '-' (B.str) + +italic :: T2T Inlines +italic = inlineMarkup inline B.emph '/' (B.str) + +code :: T2T Inlines +code = inlineMarkup ((:[]) <$> anyChar) B.code '`' id + +raw :: T2T Inlines +raw = inlineMarkup ((:[]) <$> anyChar) B.text '"' id + +tagged :: T2T Inlines +tagged = do + target <- getTarget + inlineMarkup ((:[]) <$> anyChar) (B.rawInline target) '\'' id + +-- Parser for markup indicated by a double character. +-- Inline markup is greedy and glued +-- Greedy meaning ***a*** = Bold [Str "*a*"] +-- Glued meaning that markup must be tight to content +-- Markup can't pass newlines +inlineMarkup :: Monoid a + => (T2T a) -- Content parser + -> (a -> Inlines) -- Constructor + -> Char -- Fence + -> (String -> a) -- Special Case to handle ****** + -> T2T Inlines +inlineMarkup p f c special = try $ do + start <- many1 (char c) + let l = length start + guard (l >= 2) + when (l == 2) (void $ notFollowedBy space) + -- We must make sure that there is no space before the start of the + -- closing tags + body <- optionMaybe (try $ manyTill (noneOf "\n\r") $ + (try $ lookAhead (noneOf " " >> string [c,c] ))) + case body of + Just middle -> do + lastChar <- anyChar + end <- many1 (char c) + let parser inp = parseFromString (mconcat <$> many p) inp + let start' = special (drop 2 start) + body' <- parser (middle ++ [lastChar]) + let end' = special (drop 2 end) + return $ f (start' <> body' <> end') + Nothing -> do -- Either bad or case such as ***** + guard (l >= 5) + let body' = (replicate (l - 4) c) + return $ f (special body') + +link :: T2T Inlines +link = try imageLink <|> titleLink + +-- Link with title +titleLink :: T2T Inlines +titleLink = try $ do + char '[' + notFollowedBy space + tokens <- sepBy1 (many $ noneOf " ]") space + guard (length tokens >= 2) + char ']' + let link' = last tokens + guard (length link' > 0) + let tit = concat (intersperse " " (init tokens)) + return $ B.link link' "" (B.text tit) + +-- Link with image +imageLink :: T2T Inlines +imageLink = try $ do + char '[' + body <- image + many1 space + l <- manyTill (noneOf "\n\r ") (char ']') + return (B.link l "" body) + +macro :: T2T Inlines +macro = try $ do + name <- string "%%" *> oneOfStringsCI (map fst commands) + optional (try $ enclosed (char '(') (char ')') anyChar) + lookAhead (spaceChar <|> oneOf specialChars <|> newline) + maybe (return mempty) (\f -> B.str <$> asks f) (lookup name commands) + where + commands = [ ("date", date), ("mtime", mtime) + , ("infile", infile), ("outfile", outfile)] + +-- raw URLs in text are automatically linked +url :: T2T Inlines +url = try $ do + (rawUrl, escapedUrl) <- (try uri <|> emailAddress) + return $ B.link rawUrl "" (B.str escapedUrl) + +uri :: T2T (String, String) +uri = try $ do + address <- t2tURI + return (address, escapeURI address) + +-- The definition of a URI in the T2T source differs from the +-- actual definition. This is a transcription of the definition in +-- the source of v2.6 +--isT2TURI :: String -> Bool +--isT2TURI (parse t2tURI "" -> Right _) = True +--isT2TURI _ = False + +t2tURI :: T2T String +t2tURI = do + start <- try ((++) <$> proto <*> urlLogin) <|> guess + domain <- many1 chars + sep <- many (char '/') + form' <- option mempty ((:) <$> char '?' <*> many1 form) + anchor' <- option mempty ((:) <$> char '#' <*> many anchor) + return (start ++ domain ++ sep ++ form' ++ anchor') + where + protos = ["http", "https", "ftp", "telnet", "gopher", "wais"] + proto = (++) <$> oneOfStrings protos <*> string "://" + guess = (++) <$> (((++) <$> stringAnyCase "www" <*> option mempty ((:[]) <$> oneOf "23")) + <|> stringAnyCase "ftp") <*> ((:[]) <$> char '.') + login = alphaNum <|> oneOf "_.-" + pass = many (noneOf " @") + chars = alphaNum <|> oneOf "%._/~:,=$@&+-" + anchor = alphaNum <|> oneOf "%._0" + form = chars <|> oneOf ";*" + urlLogin = option mempty $ try ((\x y z -> x ++ y ++ [z]) <$> many1 login <*> option mempty ((:) <$> char ':' <*> pass) <*> char '@') + + +image :: T2T Inlines +image = try $ do + -- List taken from txt2tags source + let extensions = [".jpg", ".jpeg", ".gif", ".png", ".eps", ".bmp"] + char '[' + path <- manyTill (noneOf "\n\t\r ") (try $ lookAhead (oneOfStrings extensions)) + ext <- oneOfStrings extensions + char ']' + return $ B.image (path ++ ext) "" mempty + +-- Characters used in markup +specialChars :: String +specialChars = "%*-_/|:+" + +tab :: T2T Char +tab = char '\t' + +space :: T2T Char +space = char ' ' + +spaces :: T2T String +spaces = many space + +endline :: T2T Inlines +endline = try $ do + newline + notFollowedBy blankline + notFollowedBy hrule + notFollowedBy title + notFollowedBy verbatim + notFollowedBy rawBlock + notFollowedBy taggedBlock + notFollowedBy quote + notFollowedBy list + notFollowedBy table + return $ B.space + +str :: T2T Inlines +str = try $ do + B.str <$> many1 (noneOf $ specialChars ++ "\n\r ") + +whitespace :: T2T Inlines +whitespace = try $ B.space <$ spaceChar + +symbol :: T2T Inlines +symbol = B.str . (:[]) <$> oneOf specialChars + +-- Utility + +getTarget :: T2T String +getTarget = do + mv <- lookupMeta "target" . stateMeta <$> getState + let MetaString target = fromMaybe (MetaString "html") mv + return target + +atStart :: T2T () +atStart = (sourceColumn <$> getPosition) >>= guard . (== 1) + +ignoreSpacesCap :: T2T String -> T2T String +ignoreSpacesCap p = map toLower <$> (spaces *> p <* spaces) + diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index 2a2f56281..1a4e037cf 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -32,53 +32,54 @@ the HTML using data URIs. -} module Text.Pandoc.SelfContained ( makeSelfContained ) where import Text.HTML.TagSoup -import Network.URI (isURI, escapeURIString) +import Network.URI (isURI, escapeURIString, URI(..), parseURI) import Data.ByteString.Base64 import qualified Data.ByteString.Char8 as B import Data.ByteString (ByteString) -import System.FilePath (takeExtension, dropExtension, takeDirectory, (</>)) +import System.FilePath (takeExtension, takeDirectory, (</>)) import Data.Char (toLower, isAscii, isAlphaNum) import Codec.Compression.GZip as Gzip import qualified Data.ByteString.Lazy as L -import Text.Pandoc.Shared (renderTags', openURL, readDataFile, err) +import Text.Pandoc.Shared (renderTags', err, fetchItem') +import Text.Pandoc.MediaBag (MediaBag) import Text.Pandoc.UTF8 (toString, fromString) -import Text.Pandoc.MIME (getMimeType) -import System.Directory (doesFileExist) +import Text.Pandoc.Options (WriterOptions(..)) isOk :: Char -> Bool isOk c = isAscii c && isAlphaNum c -convertTag :: Maybe FilePath -> Tag String -> IO (Tag String) -convertTag userdata t@(TagOpen tagname as) +convertTag :: MediaBag -> Maybe String -> Tag String -> IO (Tag String) +convertTag media sourceURL t@(TagOpen tagname as) | tagname `elem` ["img", "embed", "video", "input", "audio", "source"] = do as' <- mapM processAttribute as return $ TagOpen tagname as' where processAttribute (x,y) = if x == "src" || x == "href" || x == "poster" then do - (raw, mime) <- getRaw userdata (fromAttrib "type" t) y + (raw, mime) <- getRaw media sourceURL (fromAttrib "type" t) y let enc = "data:" ++ mime ++ ";base64," ++ toString (encode raw) return (x, enc) else return (x,y) -convertTag userdata t@(TagOpen "script" as) = +convertTag media sourceURL t@(TagOpen "script" as) = case fromAttrib "src" t of [] -> return t src -> do - (raw, mime) <- getRaw userdata (fromAttrib "type" t) src + (raw, mime) <- getRaw media sourceURL (fromAttrib "type" t) src let enc = "data:" ++ mime ++ "," ++ escapeURIString isOk (toString raw) return $ TagOpen "script" (("src",enc) : [(x,y) | (x,y) <- as, x /= "src"]) -convertTag userdata t@(TagOpen "link" as) = +convertTag media sourceURL t@(TagOpen "link" as) = case fromAttrib "href" t of [] -> return t src -> do - (raw, mime) <- getRaw userdata (fromAttrib "type" t) src + (raw, mime) <- getRaw media sourceURL (fromAttrib "type" t) src let enc = "data:" ++ mime ++ "," ++ escapeURIString isOk (toString raw) return $ TagOpen "link" (("href",enc) : [(x,y) | (x,y) <- as, x /= "href"]) -convertTag _ t = return t +convertTag _ _ t = return t -- NOTE: This is really crude, it doesn't respect CSS comments. -cssURLs :: Maybe FilePath -> FilePath -> ByteString -> IO ByteString -cssURLs userdata d orig = +cssURLs :: MediaBag -> Maybe String -> FilePath -> ByteString + -> IO ByteString +cssURLs media sourceURL d orig = case B.breakSubstring "url(" orig of (x,y) | B.null y -> return orig | otherwise -> do @@ -91,33 +92,21 @@ cssURLs userdata d orig = let url' = if isURI url then url else d </> url - (raw, mime) <- getRaw userdata "" url' - rest <- cssURLs userdata d v + (raw, mime) <- getRaw media sourceURL "" url' + rest <- cssURLs media sourceURL d v let enc = "data:" `B.append` fromString mime `B.append` ";base64," `B.append` (encode raw) return $ x `B.append` "url(" `B.append` enc `B.append` rest -getItem :: Maybe FilePath -> String -> IO (ByteString, Maybe String) -getItem userdata f = - if isURI f - then openURL f >>= either handleErr return - else do - -- strip off trailing query or fragment part, if relative URL. - -- this is needed for things like cmunrm.eot?#iefix, - -- which is used to get old versions of IE to work with web fonts. - let f' = takeWhile (\c -> c /= '?' && c /= '#') f - let mime = case takeExtension f' of - ".gz" -> getMimeType $ dropExtension f' - x -> getMimeType x - exists <- doesFileExist f' - cont <- if exists then B.readFile f' else readDataFile userdata f' - return (cont, mime) - where handleErr e = err 61 $ "Failed to retrieve " ++ f ++ "\n" ++ show e - -getRaw :: Maybe FilePath -> String -> String -> IO (ByteString, String) -getRaw userdata mimetype src = do +getRaw :: MediaBag -> Maybe String -> String -> String + -> IO (ByteString, String) +getRaw media sourceURL mimetype src = do let ext = map toLower $ takeExtension src - (raw, respMime) <- getItem userdata src + fetchResult <- fetchItem' media sourceURL src + (raw, respMime) <- case fetchResult of + Left msg -> err 67 $ "Could not fetch " ++ src ++ + "\n" ++ show msg + Right x -> return x let raw' = if ext == ".gz" then B.concat $ L.toChunks $ Gzip.decompress $ L.fromChunks $ [raw] @@ -127,21 +116,22 @@ getRaw userdata mimetype src = do $ "Could not determine mime type for `" ++ src ++ "'" (x, Nothing) -> x (_, Just x ) -> x + let cssSourceURL = case parseURI src of + Just u + | uriScheme u `elem` ["http:","https:"] -> + Just $ show u{ uriPath = "", + uriQuery = "", + uriFragment = "" } + _ -> Nothing result <- if mime == "text/css" - then cssURLs userdata (takeDirectory src) raw' + then cssURLs media cssSourceURL (takeDirectory src) raw' else return raw' return (result, mime) -- | Convert HTML into self-contained HTML, incorporating images, --- scripts, and CSS using data: URIs. Items specified using absolute --- URLs will be downloaded; those specified using relative URLs will --- be sought first relative to the working directory, then relative --- to the user data directory (if the first parameter is 'Just' --- a directory), and finally relative to pandoc's default data --- directory. -makeSelfContained :: Maybe FilePath -> String -> IO String -makeSelfContained userdata inp = do +-- scripts, and CSS using data: URIs. +makeSelfContained :: WriterOptions -> String -> IO String +makeSelfContained opts inp = do let tags = parseTags inp - out' <- mapM (convertTag userdata) tags + out' <- mapM (convertTag (writerMediaBag opts) (writerSourceURL opts)) tags return $ renderTags' out' - diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index bb13836f2..f0e5bbe5d 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -59,6 +59,7 @@ module Text.Pandoc.Shared ( normalizeBlocks, removeFormatting, stringify, + capitalize, compactify, compactify', compactify'DL, @@ -77,16 +78,20 @@ module Text.Pandoc.Shared ( readDataFile, readDataFileUTF8, fetchItem, + fetchItem', openURL, -- * Error handling err, warn, -- * Safe read - safeRead + safeRead, + -- * Temp directory + withTempDir ) where import Text.Pandoc.Definition import Text.Pandoc.Walk +import Text.Pandoc.MediaBag (MediaBag, lookupMedia) import Text.Pandoc.Builder (Inlines, Blocks, ToMetaValue(..)) import qualified Text.Pandoc.Builder as B import qualified Text.Pandoc.UTF8 as UTF8 @@ -97,11 +102,11 @@ import Data.Char ( toLower, isLower, isUpper, isAlpha, import Data.List ( find, isPrefixOf, intercalate ) import qualified Data.Map as M import Network.URI ( escapeURIString, isURI, nonStrictRelativeTo, - unEscapeString, parseURIReference ) + unEscapeString, parseURIReference, isAllowedInURI ) import qualified Data.Set as Set import System.Directory import Text.Pandoc.MIME (getMimeType) -import System.FilePath ( (</>), takeExtension, dropExtension ) +import System.FilePath ( (</>), takeExtension, dropExtension) import Data.Generics (Typeable, Data) import qualified Control.Monad.State as S import qualified Control.Exception as E @@ -110,6 +115,7 @@ import Text.Pandoc.Pretty (charWidth) import System.Locale (defaultTimeLocale) import Data.Time import System.IO (stderr) +import System.IO.Temp import Text.HTML.TagSoup (renderTagsOptions, RenderOptions(..), Tag(..), renderOptions) import qualified Data.ByteString as BS @@ -117,6 +123,7 @@ import qualified Data.ByteString.Char8 as B8 import Text.Pandoc.Compat.Monoid import Data.ByteString.Base64 (decodeLenient) import Data.Sequence (ViewR(..), ViewL(..), viewl, viewr) +import qualified Data.Text as T (toUpper, pack, unpack) #ifdef EMBED_DATA_FILES import Text.Pandoc.Data (dataFiles) @@ -522,6 +529,17 @@ stringify = query go . walk deNote deNote (Note _) = Str "" deNote x = x +-- | Bring all regular text in a pandoc structure to uppercase. +-- +-- This function correctly handles cases where a lowercase character doesn't +-- match to a single uppercase character – e.g. “Straße” would be converted +-- to “STRASSE”, not “STRAßE”. +capitalize :: Walkable Inline a => a -> a +capitalize = walk go + where go :: Inline -> Inline + go (Str s) = Str (T.unpack $ T.toUpper $ T.pack s) + go x = x + -- | Change final list item from @Para@ to @Plain@ if the list contains -- no other @Para@ blocks. compactify :: [[Block]] -- ^ List of list items (each a list of blocks) @@ -553,20 +571,22 @@ compactify' items = _ -> items _ -> items --- | Like @compactify'@, but akts on items of definition lists. +-- | Like @compactify'@, but acts on items of definition lists. compactify'DL :: [(Inlines, [Blocks])] -> [(Inlines, [Blocks])] compactify'DL items = let defs = concatMap snd items - defBlocks = reverse $ concatMap B.toList defs - in case defBlocks of - (Para x:_) -> if not $ any isPara (drop 1 defBlocks) - then let (t,ds) = last items - lastDef = B.toList $ last ds - ds' = init ds ++ - [B.fromList $ init lastDef ++ [Plain x]] - in init items ++ [(t, ds')] - else items - _ -> items + in case reverse (concatMap B.toList defs) of + (Para x:xs) + | not (any isPara xs) -> + let (t,ds) = last items + lastDef = B.toList $ last ds + ds' = init ds ++ + if null lastDef + then [B.fromList lastDef] + else [B.fromList $ init lastDef ++ [Plain x]] + in init items ++ [(t, ds')] + | otherwise -> items + _ -> items isPara :: Block -> Bool isPara (Para _) = True @@ -759,21 +779,31 @@ readDataFileUTF8 userDir fname = -- Returns raw content and maybe mime type. fetchItem :: Maybe String -> String -> IO (Either E.SomeException (BS.ByteString, Maybe String)) -fetchItem sourceURL s - | isURI s = openURL s - | otherwise = - case sourceURL >>= parseURIReference of - Just u -> case parseURIReference s of - Just s' -> openURL $ show $ - s' `nonStrictRelativeTo` u - Nothing -> openURL $ show u ++ "/" ++ s - Nothing -> E.try readLocalFile +fetchItem sourceURL s = + case (sourceURL >>= parseURIReference . ensureEscaped, ensureEscaped s) of + (_, s') | isURI s' -> openURL s' + (Just u, s') -> -- try fetching from relative path at source + case parseURIReference s' of + Just u' -> openURL $ show $ u' `nonStrictRelativeTo` u + Nothing -> openURL s' -- will throw error + (Nothing, _) -> E.try readLocalFile -- get from local file system where readLocalFile = do - let mime = case takeExtension s of - ".gz" -> getMimeType $ dropExtension s - x -> getMimeType x - cont <- BS.readFile $ unEscapeString s + cont <- BS.readFile fp return (cont, mime) + dropFragmentAndQuery = takeWhile (\c -> c /= '?' && c /= '#') + fp = unEscapeString $ dropFragmentAndQuery s + mime = case takeExtension fp of + ".gz" -> getMimeType $ dropExtension fp + x -> getMimeType x + ensureEscaped = escapeURIString isAllowedInURI + +-- | Like 'fetchItem', but also looks for items in a 'MediaBag'. +fetchItem' :: MediaBag -> Maybe String -> String + -> IO (Either E.SomeException (BS.ByteString, Maybe String)) +fetchItem' media sourceURL s = do + case lookupMedia s media of + Nothing -> fetchItem sourceURL s + Just (mime, bs) -> return $ Right (BS.concat $ toChunks bs, Just mime) -- | Read from a URL and return raw data and maybe mime type. openURL :: String -> IO (Either E.SomeException (BS.ByteString, Maybe String)) @@ -833,3 +863,15 @@ safeRead s = case reads s of (d,x):_ | all isSpace x -> return d _ -> fail $ "Could not read `" ++ s ++ "'" + +-- +-- Temp directory +-- + +withTempDir :: String -> (FilePath -> IO a) -> IO a +withTempDir = +#ifdef _WINDOWS + withTempDirectory "." +#else + withSystemTempDirectory +#endif diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index de31e462e..6be6eb1d3 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -481,17 +481,30 @@ writeOpenXML opts (Pandoc meta blocks) = do _ -> [] let auths = docAuthors meta let dat = docDate meta + let abstract' = case lookupMeta "abstract" meta of + Just (MetaBlocks bs) -> bs + Just (MetaInlines ils) -> [Plain ils] + _ -> [] + let subtitle' = case lookupMeta "subtitle" meta of + Just (MetaBlocks [Plain xs]) -> xs + Just (MetaBlocks [Para xs]) -> xs + Just (MetaInlines xs) -> xs + _ -> [] title <- withParaProp (pStyle "Title") $ blocksToOpenXML opts [Para tit | not (null tit)] - authors <- withParaProp (pStyle "Authors") $ blocksToOpenXML opts - [Para (intercalate [LineBreak] auths) | not (null auths)] + subtitle <- withParaProp (pStyle "Subtitle") $ blocksToOpenXML opts [Para subtitle' | not (null subtitle')] + authors <- withParaProp (pStyle "Author") $ blocksToOpenXML opts $ + map Para auths date <- withParaProp (pStyle "Date") $ blocksToOpenXML opts [Para dat | not (null dat)] + abstract <- if null abstract' + then return [] + else withParaProp (pStyle "Abstract") $ blocksToOpenXML opts abstract' let convertSpace (Str x : Space : Str y : xs) = Str (x ++ " " ++ y) : xs convertSpace (Str x : Str y : xs) = Str (x ++ y) : xs convertSpace xs = xs let blocks' = bottomUp convertSpace $ blocks doc' <- blocksToOpenXML opts blocks' notes' <- reverse `fmap` gets stFootnotes - let meta' = title ++ authors ++ date + let meta' = title ++ subtitle ++ authors ++ date ++ abstract return (meta' ++ doc', notes') -- | Convert a list of Pandoc blocks to OpenXML. @@ -817,7 +830,8 @@ inlineToOpenXML opts (Image alt (src, tit)) = do case M.lookup src imgs of Just (_,_,_,elt,_) -> return [elt] Nothing -> do - res <- liftIO $ fetchItem (writerSourceURL opts) src + res <- liftIO $ + fetchItem' (writerMediaBag opts) (writerSourceURL opts) src case res of Left (_ :: E.SomeException) -> do liftIO $ warn $ "Could not find image `" ++ src ++ "', skipping..." diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index ec206086a..34a6dcb2f 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -360,7 +360,8 @@ writeEPUB opts doc@(Pandoc meta _) = do walkM (transformBlock opts' mediaRef) pics <- readIORef mediaRef let readPicEntry entries (oldsrc, newsrc) = do - res <- fetchItem (writerSourceURL opts') oldsrc + res <- fetchItem' (writerMediaBag opts') + (writerSourceURL opts') oldsrc case res of Left _ -> do warn $ "Could not find media `" ++ oldsrc ++ "', skipping..." @@ -792,7 +793,7 @@ transformInline opts mediaRef (Image lab (src,tit)) = do return $ Image lab (newsrc, tit) transformInline opts _ (x@(Math _ _)) | WebTeX _ <- writerHTMLMathMethod opts = do - raw <- makeSelfContained Nothing $ writeHtmlInline opts x + raw <- makeSelfContained opts $ writeHtmlInline opts x return $ RawInline (Format "html") raw transformInline opts mediaRef (RawInline fmt raw) | fmt == Format "html" = do diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index 803617f95..7a9bff4fe 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -28,7 +28,7 @@ module Text.Pandoc.Writers.FB2 (writeFB2) where import Control.Monad.State (StateT, evalStateT, get, modify) import Control.Monad.State (liftM, liftM2, liftIO) import Data.ByteString.Base64 (encode) -import Data.Char (toUpper, toLower, isSpace, isAscii, isControl) +import Data.Char (toLower, isSpace, isAscii, isControl) import Data.List (intersperse, intercalate, isPrefixOf) import Data.Either (lefts, rights) import Network.Browser (browse, request, setAllowRedirects, setOutHandler) @@ -44,8 +44,7 @@ import qualified Text.XML.Light.Cursor as XC import Text.Pandoc.Definition import Text.Pandoc.Options (WriterOptions(..), HTMLMathMethod(..), def) -import Text.Pandoc.Shared (orderedListMarkers, isHeaderBlock) -import Text.Pandoc.Walk +import Text.Pandoc.Shared (orderedListMarkers, isHeaderBlock, capitalize) -- | Data to be written at the end of the document: -- (foot)notes, URLs, references, images. @@ -421,10 +420,6 @@ indent = indentBlock indentLines ins = let lns = split isLineBreak ins :: [[Inline]] in intercalate [LineBreak] $ map ((Str spacer):) lns -capitalize :: Inline -> Inline -capitalize (Str xs) = Str $ map toUpper xs -capitalize x = x - -- | Convert a Pandoc's Inline element to FictionBook XML representation. toXml :: Inline -> FBM [Content] toXml (Str s) = return [txt s] @@ -434,7 +429,7 @@ toXml (Strong ss) = list `liftM` wrap "strong" ss toXml (Strikeout ss) = list `liftM` wrap "strikethrough" ss toXml (Superscript ss) = list `liftM` wrap "sup" ss toXml (Subscript ss) = list `liftM` wrap "sub" ss -toXml (SmallCaps ss) = cMapM toXml $ walk capitalize ss +toXml (SmallCaps ss) = cMapM toXml $ capitalize ss toXml (Quoted SingleQuote ss) = do -- FIXME: should be language-specific inner <- cMapM toXml ss return $ [txt "‘"] ++ inner ++ [txt "’"] diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 0197d5db6..ea704c91d 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -742,7 +742,7 @@ inlineToLaTeX (Quoted qt lst) = do else char '\x2018' <> inner <> char '\x2019' inlineToLaTeX (Str str) = liftM text $ stringToLaTeX TextString str inlineToLaTeX (Math InlineMath str) = - return $ char '$' <> text str <> char '$' + return $ "\\(" <> text str <> "\\)" inlineToLaTeX (Math DisplayMath str) = return $ "\\[" <> text str <> "\\]" inlineToLaTeX (RawInline f str) diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index 37f148c0a..a859267cc 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -37,7 +37,7 @@ import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Shared import Text.Pandoc.Writers.Shared import Text.Pandoc.Options -import Text.Pandoc.Parsing hiding (blankline, char, space) +import Text.Pandoc.Parsing hiding (blankline, blanklines, char, space) import Data.List ( group, isPrefixOf, find, intersperse, transpose, sortBy ) import Data.Char ( isSpace, isPunctuation ) import Data.Ord ( comparing ) @@ -77,27 +77,13 @@ writePlain :: WriterOptions -> Pandoc -> String writePlain opts document = evalState (pandocToMarkdown opts{ writerExtensions = Set.delete Ext_escaped_line_breaks $ + Set.delete Ext_pipe_tables $ + Set.delete Ext_raw_html $ + Set.delete Ext_footnotes $ + Set.delete Ext_tex_math_dollars $ + Set.delete Ext_citations $ writerExtensions opts } - document') def{ stPlain = True } - where document' = plainify document - -plainify :: Pandoc -> Pandoc -plainify = walk go - where go :: Inline -> Inline - go (Emph xs) = Span ("",[],[]) xs - go (Strong xs) = Span ("",[],[]) xs - go (Strikeout xs) = Span ("",[],[]) xs - go (Superscript xs) = Span ("",[],[]) xs - go (Subscript xs) = Span ("",[],[]) xs - go (SmallCaps xs) = Span ("",[],[]) xs - go (Span _ xs) = Span ("",[],[]) xs - go (Code _ s) = Str s - go (Math _ s) = Str s - go (RawInline _ _) = Str "" - go (Link xs _) = Span ("",[],[]) xs - go (Image xs _) = Span ("",[],[]) $ [Str "["] ++ xs ++ [Str "]"] - go (Cite _ cits) = Span ("",[],[]) cits - go x = x + document) def{ stPlain = True } pandocTitleBlock :: Doc -> [Doc] -> Doc -> Doc pandocTitleBlock tit auths dat = @@ -188,7 +174,7 @@ pandocToMarkdown opts (Pandoc meta blocks) = do then tableOfContents opts headerBlocks else empty -- Strip off final 'references' header if markdown citations enabled - let blocks' = if not isPlain && isEnabled Ext_citations opts + let blocks' = if isEnabled Ext_citations opts then case reverse blocks of (Div (_,["references"],_) _):xs -> reverse xs _ -> blocks @@ -309,9 +295,9 @@ blockToMarkdown :: WriterOptions -- ^ Options -> State WriterState Doc blockToMarkdown _ Null = return empty blockToMarkdown opts (Div attrs ils) = do - isPlain <- gets stPlain + plain <- gets stPlain contents <- blockListToMarkdown opts ils - return $ if isPlain || not (isEnabled Ext_markdown_in_html_blocks opts) + return $ if plain || not (isEnabled Ext_markdown_in_html_blocks opts) then contents <> blankline else tagWithAttrs "div" attrs <> blankline <> contents <> blankline <> "</div>" <> blankline @@ -338,21 +324,22 @@ blockToMarkdown opts (Para inlines) = (<> blankline) `fmap` blockToMarkdown opts (Plain inlines) blockToMarkdown opts (RawBlock f str) | f == "html" = do - st <- get - if stPlain st - then return empty - else return $ if isEnabled Ext_markdown_attribute opts + plain <- gets stPlain + return $ if plain + then empty + else if isEnabled Ext_markdown_attribute opts then text (addMarkdownAttribute str) <> text "\n" else text str <> text "\n" | f `elem` ["latex", "tex", "markdown"] = do - st <- get - if stPlain st - then return empty - else return $ text str <> text "\n" + plain <- gets stPlain + return $ if plain + then empty + else text str <> text "\n" blockToMarkdown _ (RawBlock _ _) = return empty -blockToMarkdown _ HorizontalRule = - return $ blankline <> text "* * * * *" <> blankline +blockToMarkdown opts HorizontalRule = do + return $ blankline <> text (replicate (writerColumns opts) '-') <> blankline blockToMarkdown opts (Header level attr inlines) = do + plain <- gets stPlain -- we calculate the id that would be used by auto_identifiers -- so we know whether to print an explicit identifier ids <- gets stIds @@ -368,18 +355,19 @@ blockToMarkdown opts (Header level attr inlines) = do space <> attrsToMarkdown attr | otherwise -> empty contents <- inlineListToMarkdown opts inlines - st <- get let setext = writerSetextHeaders opts return $ nowrap $ case level of - 1 | setext -> + 1 | plain -> blanklines 3 <> contents <> blanklines 2 + | setext -> contents <> attr' <> cr <> text (replicate (offset contents) '=') <> blankline - 2 | setext -> + 2 | plain -> blanklines 2 <> contents <> blankline + | setext -> contents <> attr' <> cr <> text (replicate (offset contents) '-') <> blankline -- ghc interprets '#' characters in column 1 as linenum specifiers. - _ | stPlain st || isEnabled Ext_literate_haskell opts -> + _ | plain || isEnabled Ext_literate_haskell opts -> contents <> blankline _ -> text (replicate level '#') <> space <> contents <> attr' <> blankline blockToMarkdown opts (CodeBlock (_,classes,_) str) @@ -409,14 +397,12 @@ blockToMarkdown opts (CodeBlock attribs str) = return $ (_,(cls:_),_) -> " " <> text cls _ -> empty blockToMarkdown opts (BlockQuote blocks) = do - st <- get + plain <- gets stPlain -- if we're writing literate haskell, put a space before the bird tracks -- so they won't be interpreted as lhs... let leader = if isEnabled Ext_literate_haskell opts then " > " - else if stPlain st - then " " - else "> " + else if plain then " " else "> " contents <- blockListToMarkdown opts blocks return $ (prefixed leader contents) <> blankline blockToMarkdown opts t@(Table caption aligns widths headers rows) = do @@ -610,8 +596,19 @@ definitionListItemToMarkdown opts (label, defs) = do let sps = case writerTabStop opts - 3 of n | n > 0 -> text $ replicate n ' ' _ -> text " " - let contents = vcat $ map (\d -> hang tabStop (leader <> sps) $ vcat d <> cr) defs' - return $ nowrap labelText <> cr <> contents <> cr + if isEnabled Ext_compact_definition_lists opts + then do + let contents = vcat $ map (\d -> hang tabStop (leader <> sps) + $ vcat d <> cr) defs' + return $ nowrap labelText <> cr <> contents <> cr + else do + let contents = vcat $ map (\d -> hang tabStop (leader <> sps) + $ vcat d <> cr) defs' + let isTight = case defs of + ((Plain _ : _): _) -> True + _ -> False + return $ blankline <> nowrap labelText <> + (if isTight then cr else blankline) <> contents <> blankline else do return $ nowrap labelText <> text " " <> cr <> vsep (map vsep defs') <> blankline @@ -626,15 +623,21 @@ blockListToMarkdown opts blocks = -- code block will be treated as a list continuation paragraph where fixBlocks (b : CodeBlock attr x : rest) | (not (isEnabled Ext_fenced_code_blocks opts) || attr == nullAttr) - && isListBlock b = - b : RawBlock "html" "<!-- -->\n" : CodeBlock attr x : - fixBlocks rest + && isListBlock b = b : commentSep : CodeBlock attr x : + fixBlocks rest + fixBlocks (b1@(BulletList _) : b2@(BulletList _) : bs) = + b1 : commentSep : fixBlocks (b2:bs) + fixBlocks (b1@(OrderedList _ _) : b2@(OrderedList _ _) : bs) = + b1 : commentSep : fixBlocks (b2:bs) + fixBlocks (b1@(DefinitionList _) : b2@(DefinitionList _) : bs) = + b1 : commentSep : fixBlocks (b2:bs) fixBlocks (x : xs) = x : fixBlocks xs fixBlocks [] = [] isListBlock (BulletList _) = True isListBlock (OrderedList _ _) = True isListBlock (DefinitionList _) = True isListBlock _ = False + commentSep = RawBlock "html" "<!-- -->\n" -- | Get reference for target; if none exists, create unique one and return. -- Prefer label if possible; otherwise, generate a unique key. @@ -672,59 +675,69 @@ escapeSpaces x = x -- | Convert Pandoc inline element to markdown. inlineToMarkdown :: WriterOptions -> Inline -> State WriterState Doc inlineToMarkdown opts (Span attrs ils) = do - st <- get + plain <- gets stPlain contents <- inlineListToMarkdown opts ils - return $ if stPlain st + return $ if plain then contents else tagWithAttrs "span" attrs <> contents <> text "</span>" inlineToMarkdown opts (Emph lst) = do + plain <- gets stPlain contents <- inlineListToMarkdown opts lst - return $ "*" <> contents <> "*" + return $ if plain + then "_" <> contents <> "_" + else "*" <> contents <> "*" inlineToMarkdown opts (Strong lst) = do - contents <- inlineListToMarkdown opts lst - return $ "**" <> contents <> "**" + plain <- gets stPlain + if plain + then inlineListToMarkdown opts $ capitalize lst + else do + contents <- inlineListToMarkdown opts lst + return $ "**" <> contents <> "**" inlineToMarkdown opts (Strikeout lst) = do contents <- inlineListToMarkdown opts lst - return $ if isEnabled Ext_strikeout opts + plain <- gets stPlain + return $ if plain || isEnabled Ext_strikeout opts then "~~" <> contents <> "~~" else "<s>" <> contents <> "</s>" inlineToMarkdown opts (Superscript lst) = do - let lst' = walk escapeSpaces lst - contents <- inlineListToMarkdown opts lst' + contents <- inlineListToMarkdown opts $ walk escapeSpaces lst return $ if isEnabled Ext_superscript opts then "^" <> contents <> "^" else "<sup>" <> contents <> "</sup>" inlineToMarkdown opts (Subscript lst) = do - let lst' = walk escapeSpaces lst - contents <- inlineListToMarkdown opts lst' + contents <- inlineListToMarkdown opts $ walk escapeSpaces lst return $ if isEnabled Ext_subscript opts then "~" <> contents <> "~" else "<sub>" <> contents <> "</sub>" inlineToMarkdown opts (SmallCaps lst) = do - contents <- inlineListToMarkdown opts lst - st <- get - return $ if stPlain st - then contents - else tagWithAttrs "span" - ("",[],[("style","font-variant:small-caps;")]) - <> contents <> text "</span>" + plain <- gets stPlain + if plain + then inlineListToMarkdown opts $ capitalize lst + else do + contents <- inlineListToMarkdown opts lst + return $ tagWithAttrs "span" + ("",[],[("style","font-variant:small-caps;")]) + <> contents <> text "</span>" inlineToMarkdown opts (Quoted SingleQuote lst) = do contents <- inlineListToMarkdown opts lst return $ "‘" <> contents <> "’" inlineToMarkdown opts (Quoted DoubleQuote lst) = do contents <- inlineListToMarkdown opts lst return $ "“" <> contents <> "”" -inlineToMarkdown opts (Code attr str) = +inlineToMarkdown opts (Code attr str) = do let tickGroups = filter (\s -> '`' `elem` s) $ group str - longest = if null tickGroups + let longest = if null tickGroups then 0 else maximum $ map length tickGroups - marker = replicate (longest + 1) '`' - spacer = if (longest == 0) then "" else " " - attrs = if isEnabled Ext_inline_code_attributes opts && attr /= nullAttr + let marker = replicate (longest + 1) '`' + let spacer = if (longest == 0) then "" else " " + let attrs = if isEnabled Ext_inline_code_attributes opts && attr /= nullAttr then attrsToMarkdown attr else empty - in return $ text (marker ++ spacer ++ str ++ spacer ++ marker) <> attrs + plain <- gets stPlain + if plain + then return $ text str + else return $ text (marker ++ spacer ++ str ++ spacer ++ marker) <> attrs inlineToMarkdown _ (Str str) = do st <- get if stPlain st @@ -737,7 +750,11 @@ inlineToMarkdown opts (Math InlineMath str) return $ "\\(" <> text str <> "\\)" | isEnabled Ext_tex_math_double_backslash opts = return $ "\\\\(" <> text str <> "\\\\)" - | otherwise = inlineListToMarkdown opts $ texMathToInlines InlineMath str + | otherwise = do + plain <- gets stPlain + inlineListToMarkdown opts $ + (if plain then makeMathPlainer else id) $ + texMathToInlines InlineMath str inlineToMarkdown opts (Math DisplayMath str) | isEnabled Ext_tex_math_dollars opts = return $ "$$" <> text str <> "$$" @@ -747,15 +764,20 @@ inlineToMarkdown opts (Math DisplayMath str) return $ "\\\\[" <> text str <> "\\\\]" | otherwise = (\x -> cr <> x <> cr) `fmap` inlineListToMarkdown opts (texMathToInlines DisplayMath str) -inlineToMarkdown opts (RawInline f str) - | f == "html" || f == "markdown" || - (isEnabled Ext_raw_tex opts && (f == "latex" || f == "tex")) = - return $ text str -inlineToMarkdown _ (RawInline _ _) = return empty -inlineToMarkdown opts (LineBreak) - | isEnabled Ext_hard_line_breaks opts = return cr - | isEnabled Ext_escaped_line_breaks opts = return $ "\\" <> cr - | otherwise = return $ " " <> cr +inlineToMarkdown opts (RawInline f str) = do + plain <- gets stPlain + if not plain && f == "html" || f == "markdown" || + (isEnabled Ext_raw_tex opts && (f == "latex" || f == "tex")) + then return $ text str + else return empty +inlineToMarkdown opts (LineBreak) = do + plain <- gets stPlain + if plain || isEnabled Ext_hard_line_breaks opts + then return cr + else return $ + if isEnabled Ext_escaped_line_breaks opts + then "\\" <> cr + else " " <> cr inlineToMarkdown _ Space = return space inlineToMarkdown opts (Cite [] lst) = inlineListToMarkdown opts lst inlineToMarkdown opts (Cite (c:cs) lst) @@ -788,6 +810,7 @@ inlineToMarkdown opts (Cite (c:cs) lst) modekey SuppressAuthor = "-" modekey _ = "" inlineToMarkdown opts (Link txt (src, tit)) = do + plain <- gets stPlain linktext <- inlineListToMarkdown opts txt let linktitle = if null tit then empty @@ -801,22 +824,29 @@ inlineToMarkdown opts (Link txt (src, tit)) = do ref <- if useRefLinks then getReference txt (src, tit) else return [] reftext <- inlineListToMarkdown opts ref return $ if useAuto - then "<" <> text srcSuffix <> ">" + then if plain + then text srcSuffix + else "<" <> text srcSuffix <> ">" else if useRefLinks then let first = "[" <> linktext <> "]" second = if txt == ref then "[]" else "[" <> reftext <> "]" in first <> second - else "[" <> linktext <> "](" <> - text src <> linktitle <> ")" + else if plain + then linktext + else "[" <> linktext <> "](" <> + text src <> linktitle <> ")" inlineToMarkdown opts (Image 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)) - return $ "!" <> linkPart + return $ if plain + then "[" <> linkPart <> "]" + else "!" <> linkPart inlineToMarkdown opts (Note contents) = do modify (\st -> st{ stNotes = contents : stNotes st }) st <- get @@ -824,3 +854,9 @@ inlineToMarkdown opts (Note contents) = do if isEnabled Ext_footnotes opts then return $ "[^" <> ref <> "]" else return $ "[" <> ref <> "]" + +makeMathPlainer :: [Inline] -> [Inline] +makeMathPlainer = walk go + where + go (Emph xs) = Span nullAttr xs + go x = x diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index cab55be9b..3f392a5d0 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -139,10 +139,14 @@ blockToMediaWiki (CodeBlock (_,classes,_) str) = do "python", "qbasic", "rails", "reg", "robots", "ruby", "sas", "scheme", "sdlbasic", "smalltalk", "smarty", "sql", "tcl", "", "thinbasic", "tsql", "vb", "vbnet", "vhdl", "visualfoxpro", "winbatch", "xml", "xpp", "z80"] - let (beg, end) = if null at - then ("<pre" ++ if null classes then ">" else " class=\"" ++ unwords classes ++ "\">", "</pre>") - else ("<source lang=\"" ++ head at ++ "\">", "</source>") - return $ beg ++ escapeString str ++ end + return $ + if null at + then "<pre" ++ (if null classes + then ">" + else " class=\"" ++ unwords classes ++ "\">") ++ + escapeString str ++ "</pre>" + else "<source lang=\"" ++ head at ++ "\">" ++ str ++ "</source>" + -- note: no escape! blockToMediaWiki (BlockQuote blocks) = do contents <- blockListToMediaWiki blocks diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 15f7c8be8..02794f76d 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -38,7 +38,7 @@ import qualified Data.ByteString.Lazy as B import Text.Pandoc.UTF8 ( fromStringLazy ) import Codec.Archive.Zip import Text.Pandoc.Options ( WriterOptions(..) ) -import Text.Pandoc.Shared ( stringify, readDataFile, fetchItem, warn ) +import Text.Pandoc.Shared ( stringify, readDataFile, fetchItem', warn ) import Text.Pandoc.ImageSize ( imageSize, sizeInPoints ) import Text.Pandoc.MIME ( getMimeType ) import Text.Pandoc.Definition @@ -131,7 +131,7 @@ writeODT opts doc@(Pandoc meta _) = do transformPicMath :: WriterOptions -> IORef [Entry] -> Inline -> IO Inline transformPicMath opts entriesRef (Image lab (src,_)) = do - res <- fetchItem (writerSourceURL opts) src + res <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src case res of Left (_ :: E.SomeException) -> do warn $ "Could not find image `" ++ src ++ "', skipping..." diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index fe241b8d7..43405ce3c 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -36,42 +36,48 @@ import Text.Pandoc.Readers.TeXMath import Text.Pandoc.Templates (renderTemplate') import Text.Pandoc.Walk import Data.List ( isSuffixOf, intercalate ) -import Data.Char ( ord, chr, isDigit, toLower ) -import System.FilePath ( takeExtension ) +import Data.Char ( ord, chr, isDigit ) import qualified Data.ByteString as B import qualified Data.Map as M import Text.Printf ( printf ) -import Network.URI ( isURI, unEscapeString ) -import qualified Control.Exception as E +import Text.Pandoc.ImageSize --- | Convert Image inlines into a raw RTF embedded image, read from a file. +-- | Convert Image inlines into a raw RTF embedded image, read from a file, +-- or a MediaBag, or the internet. -- If file not found or filetype not jpeg or png, leave the inline unchanged. -rtfEmbedImage :: Inline -> IO Inline -rtfEmbedImage x@(Image _ (src,_)) = do - let ext = map toLower (takeExtension src) - if ext `elem` [".jpg",".jpeg",".png"] && not (isURI src) - then do - let src' = unEscapeString src - imgdata <- E.catch (B.readFile src') - (\e -> let _ = (e :: E.SomeException) in return B.empty) - let bytes = map (printf "%02x") $ B.unpack imgdata - let filetype = case ext of - ".jpg" -> "\\jpegblip" - ".jpeg" -> "\\jpegblip" - ".png" -> "\\pngblip" - _ -> error "Unknown file type" - let raw = "{\\pict" ++ filetype ++ " " ++ concat bytes ++ "}" - return $ if B.null imgdata - then x - else RawInline (Format "rtf") raw - else return x -rtfEmbedImage x = return x +rtfEmbedImage :: WriterOptions -> Inline -> IO Inline +rtfEmbedImage opts x@(Image _ (src,_)) = do + result <- fetchItem' (writerMediaBag opts) (writerSourceURL opts) src + case result of + Right (imgdata, Just mime) + | mime == "image/jpeg" || mime == "image/png" -> do + let bytes = map (printf "%02x") $ B.unpack imgdata + let filetype = case mime of + "image/jpeg" -> "\\jpegblip" + "image/png" -> "\\pngblip" + _ -> error "Unknown file type" + let sizeSpec = case imageSize imgdata of + Nothing -> "" + Just sz -> "\\picw" ++ show xpx ++ + "\\pich" ++ show ypx ++ + "\\picwgoal" ++ show (xpt * 20) + ++ "\\pichgoal" ++ show (ypt * 20) + -- twip = 1/1440in = 1/20pt + where (xpx, ypx) = sizeInPixels sz + (xpt, ypt) = sizeInPoints sz + let raw = "{\\pict" ++ filetype ++ sizeSpec ++ " " ++ + concat bytes ++ "}" + return $ if B.null imgdata + then x + else RawInline (Format "rtf") raw + _ -> return x +rtfEmbedImage _ x = return x -- | Convert Pandoc to a string in rich text format, with -- images embedded as encoded binary data. writeRTFWithEmbeddedImages :: WriterOptions -> Pandoc -> IO String writeRTFWithEmbeddedImages options doc = - writeRTF options `fmap` walkM rtfEmbedImage doc + writeRTF options `fmap` walkM (rtfEmbedImage options) doc -- | Convert Pandoc to a string in rich text format. writeRTF :: WriterOptions -> Pandoc -> String diff --git a/tests/Tests/Old.hs b/tests/Tests/Old.hs index 628951423..2216ccca7 100644 --- a/tests/Tests/Old.hs +++ b/tests/Tests/Old.hs @@ -142,6 +142,10 @@ tests = [ testGroup "markdown" , test "reader" ["-r", "haddock", "-w", "native", "-s"] "haddock-reader.haddock" "haddock-reader.native" ] + , testGroup "txt2tags" + [ test "reader" ["-r", "t2t", "-w", "native"] + "txt2tags.t2t" "txt2tags.native" + ] , testGroup "other writers" $ map (\f -> testGroup f $ writerTests f) [ "opendocument" , "context" , "texinfo", "icml" , "man" , "plain" , "rtf", "org", "asciidoc" diff --git a/tests/Tests/Readers/Docx.hs b/tests/Tests/Readers/Docx.hs index 7b737f95a..efc520dba 100644 --- a/tests/Tests/Readers/Docx.hs +++ b/tests/Tests/Readers/Docx.hs @@ -5,10 +5,15 @@ import Text.Pandoc.Readers.Native import Text.Pandoc.Definition import Tests.Helpers import Test.Framework +import Test.HUnit (assertBool) +import Test.Framework.Providers.HUnit import qualified Data.ByteString.Lazy as B import Text.Pandoc.Readers.Docx import Text.Pandoc.Writers.Native (writeNative) import qualified Data.Map as M +import Text.Pandoc.MediaBag (MediaBag, lookupMedia, mediaDirectory) +import Codec.Archive.Zip +import System.FilePath (combine) -- We define a wrapper around pandoc that doesn't normalize in the -- tests. Since we do our own normalization, we want to make sure @@ -37,7 +42,8 @@ compareOutput :: ReaderOptions compareOutput opts docxFile nativeFile = do df <- B.readFile docxFile nf <- Prelude.readFile nativeFile - return $ (noNorm (readDocx opts df), noNorm (readNative nf)) + let (p, _) = readDocx opts df + return $ (noNorm p, noNorm (readNative nf)) testCompareWithOptsIO :: ReaderOptions -> String -> FilePath -> FilePath -> IO Test testCompareWithOptsIO opts name docxFile nativeFile = do @@ -51,6 +57,44 @@ testCompareWithOpts opts name docxFile nativeFile = testCompare :: String -> FilePath -> FilePath -> Test testCompare = testCompareWithOpts def +getMedia :: FilePath -> FilePath -> IO (Maybe B.ByteString) +getMedia archivePath mediaPath = do + zf <- B.readFile archivePath >>= return . toArchive + return $ findEntryByPath (combine "word" mediaPath) zf >>= (Just . fromEntry) + +compareMediaPathIO :: FilePath -> MediaBag -> FilePath -> IO Bool +compareMediaPathIO mediaPath mediaBag docxPath = do + docxMedia <- getMedia docxPath mediaPath + let mbBS = case lookupMedia mediaPath mediaBag of + Just (_, bs) -> bs + Nothing -> error ("couldn't find " ++ + mediaPath ++ + " in media bag") + docxBS = case docxMedia of + Just bs -> bs + Nothing -> error ("couldn't find " ++ + mediaPath ++ + " in media bag") + return $ mbBS == docxBS + +compareMediaBagIO :: FilePath -> IO Bool +compareMediaBagIO docxFile = do + df <- B.readFile docxFile + let (_, mb) = readDocx def df + bools <- mapM + (\(fp, _, _) -> compareMediaPathIO fp mb docxFile) + (mediaDirectory mb) + return $ and bools + +testMediaBagIO :: String -> FilePath -> IO Test +testMediaBagIO name docxFile = do + outcome <- compareMediaBagIO docxFile + return $ testCase name (assertBool + ("Media didn't match media bag in file " ++ docxFile) + outcome) + +testMediaBag :: String -> FilePath -> Test +testMediaBag name docxFile = buildTest $ testMediaBagIO name docxFile tests :: [Test] tests = [ testGroup "inlines" @@ -164,5 +208,21 @@ tests = [ testGroup "inlines" "docx.track_changes_deletion.docx" "docx.track_changes_deletion_all.native" ] + , testGroup "media" + [ testMediaBag + "image extraction" + "docx.image.docx" + ] + , testGroup "metadata" + [ testCompareWithOpts def{readerStandalone=True} + "metadata fields" + "docx.metadata.docx" + "docx.metadata.native" + , testCompareWithOpts def{readerStandalone=True} + "stop recording metadata with normal text" + "docx.metadata_after_normal.docx" + "docx.metadata_after_normal.native" + ] + ] diff --git a/tests/Tests/Readers/Txt2Tags.hs b/tests/Tests/Readers/Txt2Tags.hs new file mode 100644 index 000000000..4748cdc07 --- /dev/null +++ b/tests/Tests/Readers/Txt2Tags.hs @@ -0,0 +1,430 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Readers.Txt2Tags (tests) where + +import Text.Pandoc.Definition +import Test.Framework +import Tests.Helpers +import Tests.Arbitrary() +import Text.Pandoc.Builder +import Text.Pandoc +import Data.List (intersperse) +import Data.Monoid (mempty, mconcat) +import Text.Pandoc.Readers.Txt2Tags + +t2t :: String -> Pandoc +t2t s = readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def ('\n' : s) + +infix 4 =: +(=:) :: ToString c + => String -> (String, c) -> Test +(=:) = test t2t + +spcSep :: [Inlines] -> Inlines +spcSep = mconcat . intersperse space + +simpleTable' :: Int + -> [Blocks] + -> [[Blocks]] + -> Blocks +simpleTable' n = table "" (take n $ repeat (AlignCenter, 0.0)) + +tests :: [Test] +tests = + [ testGroup "Inlines" $ + [ "Plain String" =: + "Hello, World" =?> + para (spcSep [ "Hello,", "World" ]) + + , "Emphasis" =: + "//Planet Punk//" =?> + para (emph . spcSep $ ["Planet", "Punk"]) + + , "Strong" =: + "**Cider**" =?> + para (strong "Cider") + + , "Strong Emphasis" =: + "//**strength**//" =?> + para (emph . strong $ "strength") + + , "Strikeout" =: + "--Kill Bill--" =?> + para (strikeout . spcSep $ [ "Kill", "Bill" ]) + + , "Verbatim" =: + "``Robot.rock()``" =?> + para (code "Robot.rock()") + + , "Symbol" =: + "A * symbol" =?> + para (str "A" <> space <> str "*" <> space <> "symbol") + + , "No empty markup" =: + "//// **** ____ ---- ```` \"\"\"\" ''''" =?> + para (spcSep [ "////", "****", "____", "----", "````", "\"\"\"\"", "''''" ]) + + , "Inline markup is greedy" =: + "***** ///// _____ ----- ````` \"\"\"\"\" '''''" =?> + para (spcSep [strong "*", emph "/", emph "_" + , strikeout "-", code "`", text "\"" + , rawInline "html" "'"]) + , "Markup must be greedy" =: + "********** ////////// __________ ---------- `````````` \"\"\"\"\"\"\"\"\"\" ''''''''''" =?> + para (spcSep [strong "******", emph "//////", emph "______" + , strikeout "------", code "``````", text "\"\"\"\"\"\"" + , rawInline "html" "''''''"]) + , "Inlines must be glued" =: + "** a** **a ** ** a **" =?> + para (text "** a** **a ** ** a **") + + , "Macros: Date" =: + "%%date" =?> + para "date" + , "Macros: Mod Time" =: + "%%mtime" =?> + para "mtime" + , "Macros: Infile" =: + "%%infile" =?> + para "in" + , "Macros: Outfile" =: + "%%outfile" =?> + para "out" + , "Autolink" =: + "http://www.google.com" =?> + para (link "http://www.google.com" "" (str "http://www.google.com")) + , "Image" =: + "[image.jpg]" =?> + para (image "image.jpg" "" mempty) + + , "Link" =: + "[title http://google.com]" =?> + para (link "http://google.com" "" (str "title")) + + , "Image link" =: + "[[image.jpg] abc]" =?> + para (link "abc" "" (image "image.jpg" "" mempty)) + , "Invalid link: No trailing space" =: + "[title invalid ]" =?> + para (text "[title invalid ]") + + + ] + + , testGroup "Basic Blocks" $ + ["Paragraph, lines grouped together" =: + "A paragraph\n A blank line ends the \n current paragraph\n" + =?> para "A paragraph A blank line ends the current paragraph" + , "Paragraph, ignore leading and trailing spaces" =: + " Leading and trailing spaces are ignored. \n" =?> + para "Leading and trailing spaces are ignored." + , "Comment line in paragraph" =: + "A comment line can be placed inside a paragraph.\n% this comment will be ignored \nIt will not affect it.\n" + =?> para "A comment line can be placed inside a paragraph. It will not affect it." + , "Paragraph" =: + "Paragraph\n" =?> + para "Paragraph" + + , "First Level Header" =: + "+ Headline +\n" =?> + header 1 "Headline" + + , "Third Level Header" =: + "=== Third Level Headline ===\n" =?> + header 3 ("Third" <> space <> + "Level" <> space <> + "Headline") + + , "Header with label" =: + "= header =[label]" =?> + headerWith ("label", [], []) 1 ("header") + + , "Invalid header, mismatched delimiters" =: + "== header =" =?> + para (text "== header =") + + , "Invalid header, spaces in label" =: + "== header ==[ haha ]" =?> + para (text "== header ==[ haha ]") + + , "Invalid header, invalid label character" =: + "== header ==[lab/el]" =?> + para (text "== header ==[lab/el]") + , "Headers not preceded by a blank line" =: + unlines [ "++ eat dinner ++" + , "Spaghetti and meatballs tonight." + , "== walk dog ==" + ] =?> + mconcat [ header 2 ("eat" <> space <> "dinner") + , para $ spcSep [ "Spaghetti", "and", "meatballs", "tonight." ] + , header 2 ("walk" <> space <> "dog") + ] + + , "Paragraph starting with an equals" =: + "=five" =?> + para "=five" + + , "Paragraph containing asterisk at beginning of line" =: + unlines [ "lucky" + , "*star" + ] =?> + para ("lucky" <> space <> "*star") + + , "Horizontal Rule" =: + unlines [ "before" + , replicate 20 '-' + , replicate 20 '=' + , replicate 20 '_' + , "after" + ] =?> + mconcat [ para "before" + , horizontalRule + , horizontalRule + , horizontalRule + , para "after" + ] + + , "Comment Block" =: + unlines [ "%%%" + , "stuff" + , "bla" + , "%%%"] =?> + (mempty::Blocks) + + + ] + + , testGroup "Lists" $ + [ "Simple Bullet Lists" =: + ("- Item1\n" ++ + "- Item2\n") =?> + bulletList [ plain "Item1" + , plain "Item2" + ] + + , "Indented Bullet Lists" =: + (" - Item1\n" ++ + " - Item2\n") =?> + bulletList [ plain "Item1" + , plain "Item2" + ] + + + + , "Nested Bullet Lists" =: + ("- Discovery\n" ++ + " + One More Time\n" ++ + " + Harder, Better, Faster, Stronger\n" ++ + "- Homework\n" ++ + " + Around the World\n"++ + "- Human After All\n" ++ + " + Technologic\n" ++ + " + Robot Rock\n") =?> + bulletList [ mconcat + [ plain "Discovery" + , orderedList [ plain ("One" <> space <> + "More" <> space <> + "Time") + , plain ("Harder," <> space <> + "Better," <> space <> + "Faster," <> space <> + "Stronger") + ] + ] + , mconcat + [ plain "Homework" + , orderedList [ plain ("Around" <> space <> + "the" <> space <> + "World") + ] + ] + , mconcat + [ plain ("Human" <> space <> "After" <> space <> "All") + , orderedList [ plain "Technologic" + , plain ("Robot" <> space <> "Rock") + ] + ] + ] + + , "Simple Ordered List" =: + ("+ Item1\n" ++ + "+ Item2\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ plain "Item1" + , plain "Item2" + ] + in orderedListWith listStyle listStructure + + + , "Indented Ordered List" =: + (" + Item1\n" ++ + " + Item2\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ plain "Item1" + , plain "Item2" + ] + in orderedListWith listStyle listStructure + + , "Nested Ordered Lists" =: + ("+ One\n" ++ + " + One-One\n" ++ + " + One-Two\n" ++ + "+ Two\n" ++ + " + Two-One\n"++ + " + Two-Two\n") =?> + let listStyle = (1, DefaultStyle, DefaultDelim) + listStructure = [ mconcat + [ plain "One" + , orderedList [ plain "One-One" + , plain "One-Two" + ] + ] + , mconcat + [ plain "Two" + , orderedList [ plain "Two-One" + , plain "Two-Two" + ] + ] + ] + in orderedListWith listStyle listStructure + + , "Ordered List in Bullet List" =: + ("- Emacs\n" ++ + " + Org\n") =?> + bulletList [ (plain "Emacs") <> + (orderedList [ plain "Org"]) + ] + + , "Bullet List in Ordered List" =: + ("+ GNU\n" ++ + " - Freedom\n") =?> + orderedList [ (plain "GNU") <> bulletList [ (plain "Freedom") ] ] + + , "Definition List" =: + unlines [ ": PLL" + , " phase-locked loop" + , ": TTL" + , " transistor-transistor logic" + , ": PSK" + , " a digital" + ] =?> + definitionList [ ("PLL", [ plain $ "phase-locked" <> space <> "loop" ]) + , ("TTL", [ plain $ "transistor-transistor" <> space <> "logic" ]) + , ("PSK", [ plain $ "a" <> space <> "digital" ]) + ] + + + , "Loose bullet list" =: + unlines [ "- apple" + , "" + , "- orange" + , "" + , "- peach" + ] =?> + bulletList [ para "apple" + , para "orange" + , para "peach" + ] + ] + + , testGroup "Tables" + [ "Single cell table" =: + "| Test " =?> + simpleTable' 1 mempty [[plain "Test"]] + + , "Multi cell table" =: + "| One | Two |" =?> + simpleTable' 2 mempty [ [ plain "One", plain "Two" ] ] + + , "Multi line table" =: + unlines [ "| One |" + , "| Two |" + , "| Three |" + ] =?> + simpleTable' 1 mempty + [ [ plain "One" ] + , [ plain "Two" ] + , [ plain "Three" ] + ] + + , "Empty table" =: + "| |" =?> + simpleTable' 1 mempty [[mempty]] + + , "Glider Table" =: + unlines [ "| 1 | 0 | 0 |" + , "| 0 | 1 | 1 |" + , "| 1 | 1 | 0 |" + ] =?> + simpleTable' 3 mempty + [ [ plain "1", plain "0", plain "0" ] + , [ plain "0", plain "1", plain "1" ] + , [ plain "1", plain "1", plain "0" ] + ] + + + , "Table with Header" =: + unlines [ "|| Species | Status |" + , "| cervisiae | domesticated |" + , "| paradoxus | wild |" + ] =?> + simpleTable [ plain "Species", plain "Status" ] + [ [ plain "cervisiae", plain "domesticated" ] + , [ plain "paradoxus", plain "wild" ] + ] + + , "Table alignment determined by spacing" =: + unlines [ "| Numbers | Text | More |" + , "| 1 | One | foo |" + , "| 2 | Two | bar |" + ] =?> + table "" (zip [AlignCenter, AlignRight, AlignDefault] [0, 0, 0]) + [] + [ [ plain "Numbers", plain "Text", plain "More" ] + , [ plain "1" , plain "One" , plain "foo" ] + , [ plain "2" , plain "Two" , plain "bar" ] + ] + + , "Pipe within text doesn't start a table" =: + "Ceci n'est pas une | pipe " =?> + para (spcSep [ "Ceci", "n'est", "pas", "une", "|", "pipe" ]) + + + , "Table with differing row lengths" =: + unlines [ "|| Numbers | Text " + , "| 1 | One | foo |" + , "| 2 " + ] =?> + table "" (zip [AlignCenter, AlignLeft, AlignLeft] [0, 0, 0]) + [ plain "Numbers", plain "Text" , plain mempty ] + [ [ plain "1" , plain "One" , plain "foo" ] + , [ plain "2" , plain mempty , plain mempty ] + ] + + ] + + , testGroup "Blocks and fragments" + [ "Source block" =: + unlines [ "```" + , "main = putStrLn greeting" + , " where greeting = \"moin\"" + , "```" ] =?> + let code' = "main = putStrLn greeting\n" ++ + " where greeting = \"moin\"\n" + in codeBlock code' + + , "tagged block" =: + unlines [ "'''" + , "<aside>HTML5 is pretty nice.</aside>" + , "'''" + ] =?> + rawBlock "html" "<aside>HTML5 is pretty nice.</aside>\n" + + , "Quote block" =: + unlines ["\t//Niemand// hat die Absicht, eine Mauer zu errichten!" + ] =?> + blockQuote (para (spcSep [ emph "Niemand", "hat", "die", "Absicht," + , "eine", "Mauer", "zu", "errichten!" + ])) + + ] + ] diff --git a/tests/Tests/Shared.hs b/tests/Tests/Shared.hs index 8c7c31674..c9e2e21f5 100644 --- a/tests/Tests/Shared.hs +++ b/tests/Tests/Shared.hs @@ -5,6 +5,10 @@ import Text.Pandoc.Shared import Test.Framework import Tests.Helpers import Tests.Arbitrary() +import Test.Framework.Providers.HUnit +import Test.HUnit ( assertBool ) +import Text.Pandoc.Builder +import Data.Monoid tests :: [Test] tests = [ testGroup "normalize" @@ -13,6 +17,12 @@ tests = [ testGroup "normalize" , property "p_normalize_no_trailing_spaces" p_normalize_no_trailing_spaces ] + , testGroup "compactify'DL" + [ testCase "compactify'DL with empty def" $ + assertBool "compactify'DL" + (let x = [(str "word", [para (str "def"), mempty])] + in compactify'DL x == x) + ] ] p_normalize_blocks_rt :: [Block] -> Bool diff --git a/tests/Tests/Writers/LaTeX.hs b/tests/Tests/Writers/LaTeX.hs index c32ded36d..8ce73c099 100644 --- a/tests/Tests/Writers/LaTeX.hs +++ b/tests/Tests/Writers/LaTeX.hs @@ -46,7 +46,7 @@ tests = [ testGroup "code blocks" ] , testGroup "math" [ "escape |" =: para (math "\\sigma|_{\\{x\\}}") =?> - "$\\sigma|_{\\{x\\}}$" + "\\(\\sigma|_{\\{x\\}}\\)" ] , testGroup "headers" [ "unnumbered header" =: diff --git a/tests/Tests/Writers/Plain.hs b/tests/Tests/Writers/Plain.hs new file mode 100644 index 000000000..f8f1d3d90 --- /dev/null +++ b/tests/Tests/Writers/Plain.hs @@ -0,0 +1,21 @@ +{-# LANGUAGE OverloadedStrings #-} +module Tests.Writers.Plain (tests) where + +import Test.Framework +import Text.Pandoc.Builder +import Text.Pandoc +import Tests.Helpers +import Tests.Arbitrary() + + +infix 4 =: +(=:) :: (ToString a, ToPandoc a) + => String -> (a, String) -> Test +(=:) = test (writePlain def . toPandoc) + + +tests :: [Test] +tests = [ "strongly emphasized text to uppercase" + =: strong "Straße" + =?> "STRASSE" + ] diff --git a/tests/docx.image.docx b/tests/docx.image.docx Binary files differindex 060f2b204..06e4efd1a 100644 --- a/tests/docx.image.docx +++ b/tests/docx.image.docx diff --git a/tests/docx.image_no_embed.native b/tests/docx.image_no_embed.native index 063958bc7..95c73610e 100644 --- a/tests/docx.image_no_embed.native +++ b/tests/docx.image_no_embed.native @@ -1,2 +1,2 @@ -[Header 2 ("an-image",[],[]) [Str "An",Space,Str "image"] -,Para [Image [] ("word/media/image1.jpeg","")]] +[Para [Str "An",Space,Str "image:"] +,Para [Image [] ("media/image1.jpg","")]] diff --git a/tests/docx.inline_formatting.native b/tests/docx.inline_formatting.native index dc8a3d19a..22d8f79e8 100644 --- a/tests/docx.inline_formatting.native +++ b/tests/docx.inline_formatting.native @@ -1,5 +1,5 @@ [Para [Str "Regular",Space,Str "text",Space,Emph [Str "italics"],Space,Strong [Str "bold",Space,Emph [Str "bold",Space,Str "italics"]],Str "."] ,Para [Str "This",Space,Str "is",Space,SmallCaps [Str "Small",Space,Str "Caps"],Str ",",Space,Str "and",Space,Str "this",Space,Str "is",Space,Strikeout [Str "strikethrough"],Str "."] -,Para [Str "Some",Space,Str "people",Space,Str "use",Space,Span ("",[],[("underline","single")]) [Str "single",Space,Str "underlines",Space,Str "for",Space,Emph [Str "emphasis"]],Str "."] +,Para [Str "Some",Space,Str "people",Space,Str "use",Space,Emph [Str "single",Space,Str "underlines",Space,Str "for",Space,Emph [Str "emphasis"]],Str "."] ,Para [Str "Above",Space,Str "the",Space,Str "line",Space,Str "is",Space,Superscript [Str "superscript"],Space,Str "and",Space,Str "below",Space,Str "the",Space,Str "line",Space,Str "is",Space,Subscript [Str "subscript"],Str "."] ,Para [Str "A",Space,Str "line",LineBreak,Str "break."]] diff --git a/tests/docx.metadata.docx b/tests/docx.metadata.docx Binary files differnew file mode 100644 index 000000000..ccf50b475 --- /dev/null +++ b/tests/docx.metadata.docx diff --git a/tests/docx.metadata.native b/tests/docx.metadata.native new file mode 100644 index 000000000..ed7ba63cf --- /dev/null +++ b/tests/docx.metadata.native @@ -0,0 +1,2 @@ +Pandoc (Meta {unMeta = fromList [("abstract",MetaInlines [Str "This",Space,Str "is",Space,Str "a",Space,Str "test",Space,Str "of",Space,Str "how",Space,Str "this",Space,Str "all",Space,Str "works.",Space,Str "I\8217ve",Space,Str "skipped",Space,Str "lines",Space,Str "here,",Space,Str "which",Space,Str "pandoc",Space,Str "doesn\8217t",Space,Str "do,",Space,Str "but",Space,Str "which",Space,Str "shouldn\8217t",Space,Str "make",Space,Str "a",Space,Str "difference."]),("author",MetaList [MetaInlines [Str "Mary",Space,Str "Ann",Space,Str "Evans"],MetaInlines [Str "Aurore",Space,Str "Dupin"]]),("date",MetaInlines [Str "July",Space,Str "28,",Space,Str "2014"]),("title",MetaInlines [Str "This",Space,Str "Is",Space,Str "the",Space,Str "Title"])]}) +[Para [Str "And",Space,Str "now",Space,Str "this",Space,Str "is",Space,Str "normal",Space,Str "text."]] diff --git a/tests/docx.metadata_after_normal.docx b/tests/docx.metadata_after_normal.docx Binary files differnew file mode 100644 index 000000000..b94a016cb --- /dev/null +++ b/tests/docx.metadata_after_normal.docx diff --git a/tests/docx.metadata_after_normal.native b/tests/docx.metadata_after_normal.native new file mode 100644 index 000000000..f0e31f8da --- /dev/null +++ b/tests/docx.metadata_after_normal.native @@ -0,0 +1,7 @@ +Pandoc (Meta {unMeta = fromList [("abstract",MetaInlines [Str "This",Space,Str "is",Space,Str "a",Space,Str "test",Space,Str "of",Space,Str "how",Space,Str "this",Space,Str "all",Space,Str "works.",Space,Str "I\8217ve",Space,Str "skipped",Space,Str "lines",Space,Str "here,",Space,Str "which",Space,Str "pandoc",Space,Str "doesn\8217t",Space,Str "do,",Space,Str "but",Space,Str "which",Space,Str "shouldn\8217t",Space,Str "make",Space,Str "a",Space,Str "difference."]),("author",MetaList [MetaInlines [Str "Mary",Space,Str "Ann",Space,Str "Evans"],MetaInlines [Str "Aurore",Space,Str "Dupin"]]),("date",MetaInlines [Str "July",Space,Str "28,",Space,Str "2014"]),("title",MetaInlines [Str "This",Space,Str "Is",Space,Str "the",Space,Str "Title"])]}) +[Para [Str "And",Space,Str "now",Space,Str "this",Space,Str "is",Space,Str "normal",Space,Str "text."] +,Para [Str "This",Space,Str "Is",Space,Str "the",Space,Str "Title"] +,Para [Str "Mary",Space,Str "Ann",Space,Str "Evans"] +,Para [Str "Aurore",Space,Str "Dupin"] +,Para [Str "July",Space,Str "28,",Space,Str "2014"] +,Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "test",Space,Str "of",Space,Str "how",Space,Str "this",Space,Str "all",Space,Str "works.",Space,Str "I\8217ve",Space,Str "skipped",Space,Str "lines",Space,Str "here,",Space,Str "which",Space,Str "pandoc",Space,Str "doesn\8217t",Space,Str "do,",Space,Str "but",Space,Str "which",Space,Str "shouldn\8217t",Space,Str "make",Space,Str "a",Space,Str "difference."]] diff --git a/tests/test-pandoc.hs b/tests/test-pandoc.hs index c07a51ec5..e6924f6b2 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -10,12 +10,14 @@ import qualified Tests.Readers.Markdown import qualified Tests.Readers.Org import qualified Tests.Readers.RST import qualified Tests.Readers.Docx +import qualified Tests.Readers.Txt2Tags import qualified Tests.Writers.ConTeXt import qualified Tests.Writers.LaTeX import qualified Tests.Writers.HTML import qualified Tests.Writers.Docbook import qualified Tests.Writers.Native import qualified Tests.Writers.Markdown +import qualified Tests.Writers.Plain import qualified Tests.Writers.AsciiDoc import qualified Tests.Shared import qualified Tests.Walk @@ -32,6 +34,7 @@ tests = [ testGroup "Old" Tests.Old.tests , testGroup "HTML" Tests.Writers.HTML.tests , testGroup "Docbook" Tests.Writers.Docbook.tests , testGroup "Markdown" Tests.Writers.Markdown.tests + , testGroup "Plain" Tests.Writers.Plain.tests , testGroup "AsciiDoc" Tests.Writers.AsciiDoc.tests ] , testGroup "Readers" @@ -40,7 +43,7 @@ tests = [ testGroup "Old" Tests.Old.tests , testGroup "Org" Tests.Readers.Org.tests , testGroup "RST" Tests.Readers.RST.tests , testGroup "Docx" Tests.Readers.Docx.tests - + , testGroup "Txt2Tags" Tests.Readers.Txt2Tags.tests ] ] diff --git a/tests/txt2tags.native b/tests/txt2tags.native new file mode 100644 index 000000000..9f80d6d2c --- /dev/null +++ b/tests/txt2tags.native @@ -0,0 +1,551 @@ +[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 "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 "Table",Space,Str "of",Space,Str "Contents:"] +,HorizontalRule +,Header 1 ("paragraph",[],[]) [Str "Paragraph"] +,Para [Str "A",Space,Str "paragraph",Space,Str "is",Space,Str "composed",Space,Str "by",Space,Str "one",Space,Str "or",Space,Str "more",Space,Str "lines.",Space,Str "A",Space,Str "blank",Space,Str "line",Space,Str "(or",Space,Str "a",Space,Str "table,",Space,Str "or",Space,Str "a",Space,Str "list)",Space,Str "ends",Space,Str "the",Space,Str "current",Space,Str "paragraph."] +,Para [Str "Leading",Space,Str "and",Space,Str "trailing",Space,Str "spaces",Space,Str "are",Space,Str "ignored."] +,Para [Str "A",Space,Str "comment",Space,Str "line",Space,Str "can",Space,Str "be",Space,Str "placed",Space,Str "inside",Space,Str "a",Space,Str "paragraph.",Space,Str "It",Space,Str "will",Space,Str "not",Space,Str "affect",Space,Str "it."] +,Para [Str "The",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "file",Space,Str "(EOF)",Space,Str "closes",Space,Str "the",Space,Str "currently",Space,Str "open",Space,Str "paragraph."] +,Header 1 ("comment",[],[]) [Str "Comment"] +,Para [Str "%",Space,Str "not",Space,Str "on",Space,Str "the",Space,Str "line",Space,Str "beginning",Space,Str "(at",Space,Str "column",Space,Str "2)"] +,Para [Str "some",Space,Str "text",Space,Str "%",Space,Str "half",Space,Str "line",Space,Str "comments",Space,Str "are",Space,Str "not",Space,Str "allowed"] +,Header 1 ("line",[],[]) [Str "Line"] +,HorizontalRule +,HorizontalRule +,HorizontalRule +,HorizontalRule +,HorizontalRule +,HorizontalRule +,HorizontalRule +,HorizontalRule +,HorizontalRule +,HorizontalRule +,HorizontalRule +,Para [Strikeout [Str "-----"],Space,Strikeout [Str "-------",Space,Str "--------"]] +,Para [Strikeout [Str "-------+--------"]] +,Para [Str "(",Space,Strikeout [Str "----------------"],Space,Str ")"] +,Header 1 ("inline",[],[]) [Str "Inline"] +,Para [Str "i)",Space,Strong [Str "b"],Space,Emph [Str "i"],Space,Emph [Str "u"],Space,Strikeout [Str "s"],Space,Code ("",[],[]) "m",Space,Str "r",Space,RawInline (Format "html") "t",Space,Str "i)",Space,Strong [Str "bo"],Space,Emph [Str "it"],Space,Emph [Str "un"],Space,Strikeout [Str "st"],Space,Code ("",[],[]) "mo",Space,Str "ra",Space,RawInline (Format "html") "tg",Space,Str "i)",Space,Strong [Str "bold"],Space,Emph [Str "ital"],Space,Emph [Str "undr"],Space,Strikeout [Str "strk"],Space,Code ("",[],[]) "mono",Space,Str "raw",Space,RawInline (Format "html") "tggd",Space,Str "i)",Space,Strong [Str "bo",Space,Str "ld"],Space,Emph [Str "it",Space,Str "al"],Space,Emph [Str "un",Space,Str "dr"],Space,Strikeout [Str "st",Space,Str "rk"],Space,Code ("",[],[]) "mo no",Space,Str "r",Space,Str "aw",Space,RawInline (Format "html") "tg gd",Space,Str "i)",Space,Strong [Str "bo",Space,Str "*",Space,Str "ld"],Space,Emph [Str "it",Space,Str "/",Space,Str "al"],Space,Emph [Str "un",Space,Str "_",Space,Str "dr"],Space,Strikeout [Str "st",Space,Str "-",Space,Str "rk"],Space,Code ("",[],[]) "mo ` no",Space,Str "r",Space,Str "\"",Space,Str "aw",Space,RawInline (Format "html") "tg ' gd",Space,Str "i)",Space,Strong [Str "bo",Space,Str "**ld"],Space,Emph [Str "it",Space,Str "//al"],Space,Emph [Str "un",Space,Str "__dr"],Space,Strikeout [Str "st",Space,Str "--rk"],Space,Code ("",[],[]) "mo ``no",Space,Str "r",Space,Str "\"\"aw",Space,RawInline (Format "html") "tg ''gd",Space,Str "i)",Space,Strong [Str "bo",Space,Str "**",Space,Str "ld"],Space,Emph [Str "it",Space,Str "//",Space,Str "al"],Space,Emph [Str "un",Space,Str "__",Space,Str "dr"],Space,Strikeout [Str "st",Space,Str "--",Space,Str "rk"],Space,Code ("",[],[]) "mo `` no",Space,Str "r",Space,Str "\"\"",Space,Str "aw",Space,RawInline (Format "html") "tg '' gd",Space,Str "i)",Space,Strong [Str "**bold**"],Space,Emph [Str "//ital//"],Space,Emph [Str "__undr__"],Space,Strikeout [Str "--strk--"],Space,Code ("",[],[]) "``mono``",Space,Str "\"\"raw\"\"",Space,RawInline (Format "html") "''tggd''",Space,Str "i)",Space,Strong [Str "*bold*"],Space,Emph [Str "/ital/"],Space,Emph [Str "_undr_"],Space,Strikeout [Str "-strk-"],Space,Code ("",[],[]) "`mono`",Space,Str "\"raw\"",Space,RawInline (Format "html") "'tggd'"] +,Para [Str "i)",Space,Strong [Str "*"],Space,Emph [Str "/"],Space,Emph [Str "_"],Space,Strikeout [Str "-"],Space,Code ("",[],[]) "`",Space,Str "\"",Space,RawInline (Format "html") "'",Space,Str "i)",Space,Strong [Str "**"],Space,Emph [Str "//"],Space,Emph [Str "__"],Space,Strikeout [Str "--"],Space,Code ("",[],[]) "``",Space,Str "\"\"",Space,RawInline (Format "html") "''",Space,Str "i)",Space,Strong [Str "***"],Space,Emph [Str "///"],Space,Emph [Str "___"],Space,Strikeout [Str "---"],Space,Code ("",[],[]) "```",Space,Str "\"\"\"",Space,RawInline (Format "html") "'''",Space,Str "i)",Space,Strong [Str "****"],Space,Emph [Str "////"],Space,Emph [Str "____"],Space,Strikeout [Str "----"],Space,Code ("",[],[]) "````",Space,Str "\"\"\"\"",Space,RawInline (Format "html") "''''",Space,Str "i)",Space,Strong [Str "*****"],Space,Emph [Str "/////"],Space,Emph [Str "_____"],Space,Strikeout [Str "-----"],Space,Code ("",[],[]) "`````",Space,Str "\"\"\"\"\"",Space,RawInline (Format "html") "'''''",Space,Str "i)",Space,Strong [Str "******"],Space,Emph [Str "//////"],Space,Emph [Str "______"],Space,Strikeout [Str "------"],Space,Code ("",[],[]) "``````",Space,Str "\"\"\"\"\"\"",Space,RawInline (Format "html") "''''''"] +,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 "]"] +,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 [Str "[img.png",Space,Str "]"] +,Para [Str "[",Space,Str "img.png]"] +,Para [Str "[",Space,Str "img.png",Space,Str "]"] +,Header 1 ("numtitle",[],[]) [Str "Numbered",Space,Str "Title"] +,Header 1 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "1"] +,Header 2 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "2"] +,Header 3 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 4 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "4"] +,Header 5 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "5"] +,Header 1 ("lab_el-1",[],[]) [Str "Title",Space,Str "Level",Space,Str "1"] +,Header 2 ("lab_el-2",[],[]) [Str "Title",Space,Str "Level",Space,Str "2"] +,Header 3 ("lab_el-3",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 4 ("lab_el-4",[],[]) [Str "Title",Space,Str "Level",Space,Str "4"] +,Header 5 ("lab_el-5",[],[]) [Str "Title",Space,Str "Level",Space,Str "5"] +,Header 3 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 3 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 3 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 3 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 3 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 3 ("lab_el-9",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Para [Str "+Not",Space,Str "Title"] +,Para [Str "++Not",Space,Str "Title+"] +,Para [Str "+++Not",Space,Str "Title++++",Space,Str "++++++Not",Space,Str "Title",Space,Str "6++++++"] +,Para [Str "+++++++Not",Space,Str "Title",Space,Str "7+++++++",Space,Str "+Not",Space,Str "Title+",Space,Str "[label1]",Space,Str "+Not",Space,Str "Title+[",Space,Str "label",Space,Str "]",Space,Str "+Not",Space,Str "Title+[la/bel]"] +,Header 1 ("title",[],[]) [Str "Title"] +,Header 1 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "1"] +,Header 2 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "2"] +,Header 3 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 4 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "4"] +,Header 5 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "5"] +,Header 1 ("lab_el-1",[],[]) [Str "Title",Space,Str "Level",Space,Str "1"] +,Header 2 ("lab_el-2",[],[]) [Str "Title",Space,Str "Level",Space,Str "2"] +,Header 3 ("lab_el-3",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 4 ("lab_el-4",[],[]) [Str "Title",Space,Str "Level",Space,Str "4"] +,Header 5 ("lab_el-5",[],[]) [Str "Title",Space,Str "Level",Space,Str "5"] +,Header 3 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 3 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 3 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 3 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 3 ("",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Header 3 ("lab_el-9",[],[]) [Str "Title",Space,Str "Level",Space,Str "3"] +,Para [Str "=Not",Space,Str "Title"] +,Para [Str "==Not",Space,Str "Title="] +,Para [Str "===Not",Space,Str "Title====",Space,Str "======Not",Space,Str "Title",Space,Str "6======"] +,Para [Str "=======Not",Space,Str "Title",Space,Str "7=======",Space,Str "=Not",Space,Str "Title=",Space,Str "[label1]",Space,Str "=Not",Space,Str "Title=[",Space,Str "label",Space,Str "]",Space,Str "=Not",Space,Str "Title=[la/bel]"] +,Header 1 ("quote",[],[]) [Str "Quote"] +,BlockQuote + [Para [Str "To",Space,Str "quote",Space,Str "a",Space,Str "paragraph,",Space,Str "just",Space,Str "prefix",Space,Str "it",Space,Str "by",Space,Str "a",Space,Str "TAB",Space,Str "character.",Space,Str "All",Space,Str "the",Space,Str "lines",Space,Str "of",Space,Str "the",Space,Str "paragraph",Space,Str "must",Space,Str "begin",Space,Str "with",Space,Str "a",Space,Str "TAB."]] +,Para [Str "Any",Space,Str "non-tabbed",Space,Str "line",Space,Str "closes",Space,Str "the",Space,Str "quote",Space,Str "block."] +,BlockQuote + [Para [Str "The",Space,Str "number",Space,Str "of",Space,Str "leading",Space,Str "TABs",Space,Str "identifies",Space,Str "the",Space,Str "quote",Space,Str "block",Space,Str "depth.",Space,Str "This",Space,Str "is",Space,Str "quote",Space,Str "level",Space,Str "1."] + ,BlockQuote + [Para [Str "With",Space,Str "two",Space,Str "TABs,",Space,Str "we",Space,Str "are",Space,Str "on",Space,Str "the",Space,Str "quote",Space,Str "level",Space,Str "2."] + ,BlockQuote + [Para [Str "The",Space,Str "more",Space,Str "TABs,",Space,Str "more",Space,Str "deep",Space,Str "is",Space,Str "the",Space,Str "quote",Space,Str "level."] + ,BlockQuote + [Para [Str "There",Space,Str "isn't",Space,Str "a",Space,Str "limit."]]]]] +,BlockQuote + [BlockQuote + [BlockQuote + [BlockQuote + [Para [Str "This",Space,Str "quote",Space,Str "starts",Space,Str "at",Space,Str "level",Space,Str "4."]] + ,Para [Str "Then",Space,Str "its",Space,Str "depth",Space,Str "is",Space,Str "decreased."]] + ,Para [Str "Counting",Space,Str "down,",Space,Str "one",Space,Str "by",Space,Str "one."]] + ,Para [Str "Until",Space,Str "the",Space,Str "level",Space,Str "1."]] +,BlockQuote + [BlockQuote + [BlockQuote + [Para [Str "Unlike",Space,Str "lists,",Space,Str "any",Space,Str "quote",Space,Str "block",Space,Str "is",Space,Str "independent,",Space,Str "not",Space,Str "part",Space,Str "of",Space,Str "a",Space,Str "tree."]]] + ,Para [Str "The",Space,Str "TAB",Space,Str "count",Space,Str "don't",Space,Str "need",Space,Str "to",Space,Str "be",Space,Str "incremental",Space,Str "by",Space,Str "one."] + ,BlockQuote + [BlockQuote + [BlockQuote + [Para [Str "The",Space,Str "nesting",Space,Str "don't",Space,Str "need",Space,Str "to",Space,Str "follow",Space,Str "any",Space,Str "rule."]]] + ,Para [Str "Quotes",Space,Str "can",Space,Str "be",Space,Str "opened",Space,Str "and",Space,Str "closed",Space,Str "in",Space,Str "any",Space,Str "way."] + ,BlockQuote + [BlockQuote + [BlockQuote + [Para [Str "You",Space,Str "choose."]]]]]] +,BlockQuote + [Para [Str "Some",Space,Str "targets",Space,Str "(as",Space,Str "sgml)",Space,Str "don't",Space,Str "support",Space,Str "the",Space,Str "nesting",Space,Str "of",Space,Str "quotes.",Space,Str "There",Space,Str "is",Space,Str "only",Space,Str "one",Space,Str "quote",Space,Str "level."] + ,BlockQuote + [Para [Str "In",Space,Str "this",Space,Str "case,",Space,Str "no",Space,Str "matter",Space,Str "how",Space,Str "much",Space,Str "TABs",Space,Str "are",Space,Str "used",Space,Str "to",Space,Str "define",Space,Str "the",Space,Str "quote",Space,Str "block,",Space,Str "it",Space,Str "always",Space,Str "will",Space,Str "be",Space,Str "level",Space,Str "1."]]] +,BlockQuote + [Para [Str "Spaces",Space,Str "AFTER",Space,Str "the",Space,Str "TAB",Space,Str "character",Space,Str "are",Space,Str "allowed.",Space,Str "But",Space,Str "be",Space,Str "careful,",Space,Str "it",Space,Str "can",Space,Str "be",Space,Str "confusing."]] +,Para [Str "Spaces",Space,Str "BEFORE",Space,Str "the",Space,Str "TAB",Space,Str "character",Space,Str "invalidate",Space,Str "the",Space,Str "mark.",Space,Str "It's",Space,Str "not",Space,Str "quote."] +,BlockQuote + [Para [Str "Paragraph",Space,Str "breaks",Space,Str "inside",Space,Str "a",Space,Str "quote",Space,Str "aren't",Space,Str "possible."] + ,Para [Str "This",Space,Str "sample",Space,Str "are",Space,Str "two",Space,Str "separated",Space,Str "quoted",Space,Str "paragraphs,",Space,Str "not",Space,Str "a",Space,Str "quote",Space,Str "block",Space,Str "with",Space,Str "two",Space,Str "paragraphs",Space,Str "inside."]] +,BlockQuote + [Para [Str "The",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "file",Space,Str "(EOF)",Space,Str "closes",Space,Str "the",Space,Str "currently",Space,Str "open",Space,Str "quote",Space,Str "block."]] +,Header 1 ("raw",[],[]) [Str "Raw"] +,Para [Str "A raw line.\n"] +,Para [Str " Another raw line, with leading spaces.\n"] +,Para [Str "A raw area delimited\n by lines with marks.\n"] +,Para [Str "Trailing spaces and TABs after the area marks\nare allowed, but not encouraged nor documented.\n"] +,Para [Str "\"\"\"Not",Space,Str "a",Space,Str "raw",Space,Str "line,",Space,Str "need",Space,Str "one",Space,Str "space",Space,Str "after",Space,Str "mark."] +,Para [Str "\"\"\"",Space,Str "Not",Space,Str "a",Space,Str "raw",Space,Str "area.",Space,Str "The",Space,Str "marks",Space,Str "must",Space,Str "be",Space,Str "at",Space,Str "the",Space,Str "line",Space,Str "beginning,",Space,Str "no",Space,Str "leading",Space,Str "spaces.",Space,Str "\"\"\""] +,Para [Str "The end of the file (EOF) closes\nthe currently open raw area.\n"] +,Header 1 ("verbatim",[],[]) [Str "Verbatim"] +,CodeBlock ("",[],[]) "A verbatim line.\n" +,CodeBlock ("",[],[]) " Another verbatim line, with leading spaces.\n" +,CodeBlock ("",[],[]) "A verbatim area delimited\n by lines with marks.\n" +,CodeBlock ("",[],[]) "Trailing spaces and TABs after the area marks\nare allowed, but not encouraged nor documented.\n" +,Para [Str "```Not",Space,Str "a",Space,Str "verbatim",Space,Str "line,",Space,Str "need",Space,Str "one",Space,Str "space",Space,Str "after",Space,Str "mark."] +,Para [Str "```",Space,Str "Not",Space,Str "a",Space,Str "verbatim",Space,Str "area.",Space,Str "The",Space,Str "marks",Space,Str "must",Space,Str "be",Space,Str "at",Space,Str "the",Space,Str "line",Space,Str "beginning,",Space,Str "no",Space,Str "leading",Space,Str "spaces.",Space,Str "```"] +,CodeBlock ("",[],[]) "The end of the file (EOF) closes\nthe currently open verbatim area.\n" +,Header 1 ("deflist",[],[]) [Str "Definition",Space,Str "List"] +,DefinitionList + [([Str "Definition",Space,Str "list"], + [[Plain [Str "A",Space,Str "list",Space,Str "with",Space,Str "terms"]]]) + ,([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."] +,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."]] + ,[Plain [Str "There",Space,Str "must",Space,Str "be",Space,Str "one",Space,Str "space",Space,Str "after",Space,Str "the",Space,Str "hyphen."]] + ,[Plain [Str "The",Space,Str "list",Space,Str "is",Space,Str "closed",Space,Str "by",Space,Str "two",Space,Str "consecutive",Space,Str "blank",Space,Str "lines."]]] +,BulletList + [[Plain [Str "The",Space,Str "list",Space,Str "can",Space,Str "be",Space,Str "indented",Space,Str "on",Space,Str "the",Space,Str "source",Space,Str "document."]] + ,[Plain [Str "You",Space,Str "can",Space,Str "use",Space,Str "any",Space,Str "number",Space,Str "of",Space,Str "spaces."]] + ,[Plain [Str "The",Space,Str "result",Space,Str "will",Space,Str "be",Space,Str "the",Space,Str "same."]]] +,BulletList + [[Para [Str "Let",Space,Str "one",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "the",Space,Str "list",Space,Str "items."]] + ,[Para [Str "It",Space,Str "will",Space,Str "be",Space,Str "maintained",Space,Str "on",Space,Str "the",Space,Str "conversion."]] + ,[Para [Str "Some",Space,Str "targets",Space,Str "don't",Space,Str "support",Space,Str "this",Space,Str "behavior."]] + ,[Para [Str "This",Space,Str "one",Space,Str "was",Space,Str "separated",Space,Str "by",Space,Str "a",Space,Str "line",Space,Str "with",Space,Str "blanks.",Space,Str "You",Space,Str "can",Space,Str "also",Space,Str "put",Space,Str "a",Space,Str "blank",Space,Str "line",Space,Str "inside"] + ,Para [Str "the",Space,Str "item",Space,Str "contents",Space,Str "and",Space,Str "it",Space,Str "will",Space,Str "be",Space,Str "preserved."]]] +,Para [Str "-This",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "list",Space,Str "(no",Space,Str "space)"] +,Para [Str "-",Space,Str "This",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "list",Space,Str "(more",Space,Str "than",Space,Str "one",Space,Str "space)"] +,Para [Str "-",Space,Str "This",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "list",Space,Str "(a",Space,Str "TAB",Space,Str "instead",Space,Str "the",Space,Str "space)"] +,BulletList + [[BulletList + [[Plain [Str "This",Space,Str "is",Space,Str "a",Space,Str "list"]]]] + ,[OrderedList (1,DefaultStyle,DefaultDelim) + [[Plain [Str "This",Space,Str "is",Space,Str "a",Space,Str "list"]]]] + ,[DefinitionList + [([Str "This",Space,Str "is",Space,Str "a",Space,Str "list"], + [[]])]]] +,BulletList + [[Plain [Str "This",Space,Str "is",Space,Str "the",Space,Str "\"mother\"",Space,Str "list",Space,Str "first",Space,Str "item."]] + ,[Plain [Str "Here",Space,Str "is",Space,Str "the",Space,Str "second,",Space,Str "but",Space,Str "inside",Space,Str "this",Space,Str "item,"] + ,BulletList + [[Plain [Str "there",Space,Str "is",Space,Str "a",Space,Str "sublist,",Space,Str "with",Space,Str "its",Space,Str "own",Space,Str "items."]] + ,[Plain [Str "Note",Space,Str "that",Space,Str "the",Space,Str "items",Space,Str "of",Space,Str "the",Space,Str "same",Space,Str "sublist"]] + ,[Plain [Str "must",Space,Str "have",Space,Str "the",Space,Str "same",Space,Str "indentation."] + ,BulletList + [[Plain [Str "And",Space,Str "this",Space,Str "can",Space,Str "go",Space,Str "on,",Space,Str "opening",Space,Str "sublists."] + ,BulletList + [[Plain [Str "Just",Space,Str "add",Space,Str "leading",Space,Str "spaces",Space,Str "before",Space,Str "the"]] + ,[Plain [Str "hyphen",Space,Str "and",Space,Str "sublists",Space,Str "will",Space,Str "be",Space,Str "opened."]] + ,[Plain [Str "The",Space,Str "two",Space,Str "blank",Space,Str "lines",Space,Str "closes",Space,Str "them",Space,Str "all."]]]]]]]]] +,BulletList + [[Plain [Str "When",Space,Str "nesting",Space,Str "lists,",Space,Str "the",Space,Str "additional",Space,Str "spaces",Space,Str "are",Space,Str "free."]] + ,[Plain [Str "You",Space,Str "can",Space,Str "add",Space,Str "just",Space,Str "one,"] + ,BulletList + [[Plain [Str "or",Space,Str "many."] + ,BulletList + [[Plain [Str "What",Space,Str "matters",Space,Str "is",Space,Str "to",Space,Str "put",Space,Str "more",Space,Str "than",Space,Str "the",Space,Str "previous."]] + ,[Plain [Str "But",Space,Str "remember",Space,Str "that",Space,Str "the",Space,Str "other",Space,Str "items",Space,Str "of",Space,Str "the",Space,Str "same",Space,Str "list"]] + ,[Plain [Str "must",Space,Str "use",Space,Str "the",Space,Str "same",Space,Str "indentation."]]]]]]] +,BulletList + [[Plain [Str "There",Space,Str "is",Space,Str "not",Space,Str "a",Space,Str "depth",Space,Str "limit,"] + ,BulletList + [[Plain [Str "you",Space,Str "can",Space,Str "go",Space,Str "deeper",Space,Str "and",Space,Str "deeper."] + ,BulletList + [[Plain [Str "But",Space,Str "some",Space,Str "targets",Space,Str "may",Space,Str "have",Space,Str "restrictions."] + ,BulletList + [[Plain [Str "The",Space,Str "LaTeX",Space,Str "maximum",Space,Str "is",Space,Str "here,",Space,Str "4",Space,Str "levels."]]]]]]]]] +,BulletList + [[Plain [Str "Reverse",Space,Str "nesting",Space,Str "doesn't",Space,Str "work."]] + ,[Plain [Str "Because",Space,Str "a",Space,Str "sublist",Space,Str "*must*",Space,Str "have",Space,Str "a",Space,Str "mother",Space,Str "list."]] + ,[Plain [Str "It's",Space,Str "the",Space,Str "list",Space,Str "concept,",Space,Str "not",Space,Str "a",Space,Str "txt2tags",Space,Str "limitation."]] + ,[Plain [Str "All",Space,Str "this",Space,Str "sublists",Space,Str "will",Space,Str "be",Space,Str "bumped",Space,Str "to",Space,Str "mother",Space,Str "lists."]] + ,[Plain [Str "At",Space,Str "level",Space,Str "1,",Space,Str "like",Space,Str "this",Space,Str "one."]]] +,BulletList + [[Plain [Str "Level",Space,Str "1"] + ,BulletList + [[Plain [Str "Level",Space,Str "2"] + ,BulletList + [[Plain [Str "Level",Space,Str "3"] + ,BulletList + [[Plain [Str "Level",Space,Str "4"]]]] + ,[Plain [Str "Level",Space,Str "3",Space,Str "--",Space,Str "(closed",Space,Str "Level",Space,Str "4)"]]]] + ,[Plain [Str "Level",Space,Str "2",Space,Str "--",Space,Str "(closed",Space,Str "Level",Space,Str "3)"]]]] + ,[Plain [Str "Level",Space,Str "1",Space,Str "--",Space,Str "(closed",Space,Str "Level",Space,Str "2)"]]] +,BulletList + [[Plain [Str "Level",Space,Str "1"] + ,BulletList + [[Plain [Str "Level",Space,Str "2"] + ,BulletList + [[Plain [Str "Level",Space,Str "3"] + ,BulletList + [[Plain [Str "Level",Space,Str "4"]]]]]]]] + ,[Plain [Str "Level",Space,Str "1",Space,Str "--",Space,Str "(closed",Space,Str "Level",Space,Str "4,",Space,Str "Level",Space,Str "3",Space,Str "and",Space,Str "Level",Space,Str "2)"]]] +,BulletList + [[Para [Str "Level",Space,Str "1"] + ,BulletList + [[Para [Str "Level",Space,Str "2",Space,Str "--",Space,Str "blank",Space,Str "BEFORE",Space,Str "and",Space,Str "AFTER",Space,Str "(in)"] + ,BulletList + [[Plain [Str "Level",Space,Str "3"]]]]]]] +,BulletList + [[Plain [Str "Level",Space,Str "4"]]] +,BulletList + [[Para [Str "Level",Space,Str "3"]] + ,[Para [Str "Level",Space,Str "2",Space,Str "--",Space,Str "blank",Space,Str "BEFORE",Space,Str "and",Space,Str "AFTER",Space,Str "(out)"]] + ,[Para [Str "Level",Space,Str "1"] + ,BulletList + [[Para [Str "Level",Space,Str "2",Space,Str "--",Space,Str "blank",Space,Str "BEFORE",Space,Str "(spaces)",Space,Str "and",Space,Str "AFTER",Space,Str "(TAB)"] + ,BulletList + [[Plain [Str "Level",Space,Str "3"]]]]]]] +,BulletList + [[Plain [Str "Level",Space,Str "1"] + ,BulletList + [[Plain [Str "Level",Space,Str "2"] + ,BulletList + [[Plain [Str "Level",Space,Str "3"] + ,BulletList + [[Plain [Str "Level",Space,Str "4"]] + ,[Plain [Str "Level",Space,Str "3.5",Space,Str "???"]]]] + ,[Plain [Str "Level",Space,Str "3"]] + ,[Plain [Str "Level",Space,Str "2.5",Space,Str "???"]]]] + ,[Plain [Str "Level",Space,Str "2"]] + ,[Plain [Str "Level",Space,Str "1.5",Space,Str "???"]]]] + ,[Plain [Str "Level",Space,Str "1"]]] +,BulletList + [[Plain [Str "This",Space,Str "list",Space,Str "is",Space,Str "closed",Space,Str "by",Space,Str "a",Space,Str "line",Space,Str "with",Space,Str "spaces",Space,Str "and",Space,Str "other",Space,Str "with",Space,Str "TABs"]]] +,BulletList + [[Plain [Str "This",Space,Str "list",Space,Str "is",Space,Str "NOT",Space,Str "closed",Space,Str "by",Space,Str "two",Space,Str "comment",Space,Str "lines"]]] +,BulletList + [[Plain [Str "This",Space,Str "list",Space,Str "is",Space,Str "closed",Space,Str "by",Space,Str "a",Space,Str "line",Space,Str "with",Space,Str "spaces",Space,Str "and",Space,Str "TAB,"]] + ,[Plain [Str "then",Space,Str "a",Space,Str "comment",Space,Str "line,",Space,Str "then",Space,Str "an",Space,Str "empty",Space,Str "line."]]] +,BulletList + [[Plain [Str "Level",Space,Str "1"] + ,BulletList + [[Plain [Str "Level",Space,Str "2"] + ,BulletList + [[Plain [Str "Level",Space,Str "3"]]] + ,Plain [Str "-",Space,Str "Level",Space,Str "2"]]] + ,Plain [Str "-",Space,Str "Level",Space,Str "1"]]] +,Para [Str "-"] +,BulletList + [[Plain [Str "Empty",Space,Str "item",Space,Str "with",Space,Str "trailing",Space,Str "spaces."]]] +,Para [Str "-"] +,BulletList + [[Plain [Str "Empty",Space,Str "item",Space,Str "with",Space,Str "trailing",Space,Str "TAB."]]] +,Para [Str "-"] +,BulletList + [[Plain [Str "If",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "file",Space,Str "(EOF)",Space,Str "is",Space,Str "hit,"] + ,BulletList + [[Plain [Str "all",Space,Str "the",Space,Str "currently",Space,Str "opened",Space,Str "list",Space,Str "are",Space,Str "closed,"] + ,BulletList + [[Plain [Str "just",Space,Str "like",Space,Str "when",Space,Str "using",Space,Str "the",Space,Str "two",Space,Str "blank",Space,Str "lines."]]]]]]] +,Header 1 ("table",[],[]) [Str "Table"] +,Table [] [AlignRight] [0.0] + [] + [[[Plain [Str "Cell",Space,Str "1"]]]] +,Table [] [AlignCenter,AlignCenter,AlignRight] [0.0,0.0,0.0] + [] + [[[Plain [Str "Cell",Space,Str "1"]] + ,[Plain [Str "Cell",Space,Str "2"]] + ,[Plain [Str "Cell",Space,Str "3"]]]] +,Table [] [AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0] + [] + [[[Plain [Str "Cell",Space,Str "1"]] + ,[Plain [Str "Cell",Space,Str "2"]] + ,[Plain [Str "Cell",Space,Str "3"]]]] +,Para [Str "||",Space,Str "Cell",Space,Str "1",Space,Str "|",Space,Str "Cell",Space,Str "2",Space,Str "|",Space,Str "Cell",Space,Str "3",Space,Str "|"] +,Table [] [AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0] + [] + [[[Plain [Str "Cell",Space,Str "1"]] + ,[Plain [Str "Cell",Space,Str "2"]] + ,[Plain [Str "Cell",Space,Str "3"]]]] +,Table [] [AlignDefault,AlignCenter,AlignDefault] [0.0,0.0,0.0] + [[Plain [Str "Heading"]] + ,[Plain [Str "Heading"]] + ,[Plain [Str "Heading"]]] + [[[Plain [Str "<-"]] + ,[Plain [Str "--"]] + ,[Plain [Str "->"]]] + ,[[Plain [Str "--"]] + ,[Plain [Str "--"]] + ,[Plain [Str "--"]]] + ,[[Plain [Str "->"]] + ,[Plain [Str "--"]] + ,[Plain [Str "<-"]]]] +,Table [] [AlignDefault,AlignDefault,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0] + [[Plain [Str "1"]] + ,[Plain [Str "2"]] + ,[Plain [Str "3+4"]] + ,[]] + [[[Plain [Str "1"]] + ,[Plain [Str "2"]] + ,[Plain [Str "3"]] + ,[Plain [Str "4"]]] + ,[[Plain [Str "1+2+3"]] + ,[Plain [Str "4"]] + ,[] + ,[]] + ,[[Plain [Str "1"]] + ,[Plain [Str "2+3"]] + ,[Plain [Str "4"]] + ,[]] + ,[[Plain [Str "1+2+3+4"]] + ,[] + ,[] + ,[]]] +,Table [] [AlignCenter,AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0] + [] + [[[Plain [Str "0"]] + ,[Plain [Str "1"]] + ,[Plain [Str "2"]] + ,[]] + ,[[Plain [Str "4"]] + ,[Plain [Str "5"]] + ,[] + ,[Plain [Str "7"]]] + ,[[Plain [Str "8"]] + ,[] + ,[Plain [Str "A"]] + ,[Plain [Str "B"]]] + ,[[] + ,[Plain [Str "D"]] + ,[Plain [Str "E"]] + ,[Plain [Str "F"]]]] +,Table [] [AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0,0.0] + [] + [[[Plain [Str "1"]] + ,[] + ,[] + ,[] + ,[]] + ,[[Plain [Str "1"]] + ,[Plain [Str "2"]] + ,[] + ,[] + ,[]] + ,[[Plain [Str "1"]] + ,[Plain [Str "2"]] + ,[Plain [Str "3"]] + ,[] + ,[]] + ,[[Plain [Str "1"]] + ,[Plain [Str "2"]] + ,[Plain [Str "3"]] + ,[Plain [Str "4"]] + ,[]] + ,[[Plain [Str "1"]] + ,[Plain [Str "2"]] + ,[Plain [Str "3"]] + ,[Plain [Str "4"]] + ,[Plain [Str "5"]]]] +,Table [] [AlignDefault,AlignCenter,AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0,0.0] + [] + [[[Plain [Str "Jan"]] + ,[] + ,[] + ,[] + ,[]] + ,[[Plain [Str "Fev"]] + ,[] + ,[] + ,[] + ,[]] + ,[[Plain [Str "Mar"]] + ,[] + ,[] + ,[] + ,[]] + ,[[Plain [Str "Apr"]] + ,[] + ,[] + ,[] + ,[]] + ,[[Plain [Str "May"]] + ,[] + ,[] + ,[] + ,[]] + ,[[Plain [Str "20%"]] + ,[Plain [Str "40%"]] + ,[Plain [Str "60%"]] + ,[Plain [Str "80%"]] + ,[Plain [Str "100%"]]]] +,Table [] [AlignCenter,AlignDefault,AlignDefault,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0,0.0] + [] + [[[] + ,[] + ,[Plain [Str "/"]] + ,[] + ,[]] + ,[[] + ,[Plain [Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/"]] + ,[] + ,[] + ,[]] + ,[[Plain [Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/",Space,Str "/"]] + ,[] + ,[] + ,[] + ,[]] + ,[[] + ,[Plain [Str "o"]] + ,[] + ,[Plain [Str "o"]] + ,[]] + ,[[] + ,[] + ,[Plain [Str "."]] + ,[] + ,[]] + ,[[] + ,[Plain [Str "=",Space,Str "=",Space,Str "=",Space,Str "="]] + ,[] + ,[] + ,[]]] +,Table [] [AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0] + [] + [[[Plain [Str "01"]] + ,[Plain [Str "02"]] + ,[] + ,[] + ,[Plain [Str "05"]] + ,[] + ,[Plain [Str "07"]] + ,[]] + ,[[] + ,[] + ,[Plain [Str "11"]] + ,[] + ,[Plain [Str "13"]] + ,[] + ,[] + ,[Plain [Str "16"]]] + ,[[Plain [Str "17"]] + ,[] + ,[Plain [Str "19"]] + ,[Plain [Str "20"]] + ,[] + ,[] + ,[Plain [Str "23"]] + ,[]] + ,[[Plain [Str "25"]] + ,[Plain [Str "26"]] + ,[] + ,[] + ,[Plain [Str "29"]] + ,[Plain [Str "30"]] + ,[] + ,[Plain [Str "32"]]] + ,[[] + ,[] + ,[Plain [Str "35"]] + ,[] + ,[Plain [Str "37"]] + ,[] + ,[Plain [Str "39"]] + ,[Plain [Str "40"]]]] +,Table [] [AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter,AlignCenter] [0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0,0.0] + [] + [[[Plain [Str "0"]] + ,[Plain [Str "1"]] + ,[Plain [Str "2"]] + ,[Plain [Str "3"]] + ,[Plain [Str "4"]] + ,[Plain [Str "5"]] + ,[Plain [Str "6"]] + ,[Plain [Str "7"]] + ,[Plain [Str "8"]] + ,[Plain [Str "9"]] + ,[Plain [Str "A"]] + ,[Plain [Str "B"]] + ,[Plain [Str "C"]] + ,[Plain [Str "D"]] + ,[Plain [Str "E"]] + ,[Plain [Str "F"]] + ,[Plain [Str "0"]] + ,[Plain [Str "1"]] + ,[Plain [Str "2"]] + ,[Plain [Str "3"]] + ,[Plain [Str "4"]] + ,[Plain [Str "5"]] + ,[Plain [Str "6"]] + ,[Plain [Str "7"]] + ,[Plain [Str "8"]] + ,[Plain [Str "9"]] + ,[Plain [Str "A"]] + ,[Plain [Str "B"]] + ,[Plain [Str "C"]] + ,[Plain [Str "D"]] + ,[Plain [Str "E"]] + ,[Plain [Str "F"]]]] +,Table [] [AlignCenter] [0.0] + [] + [[[]] + ,[[]] + ,[[]]] +,Para [Str "|this|is|not|a|table|"] +,Para [Str "|this|",Space,Str "is|",Space,Str "not|",Space,Str "a|",Space,Str "table|"] +,Para [Str "|this",Space,Str "|is",Space,Str "|not",Space,Str "|a",Space,Str "|table",Space,Str "|"] +,Para [Str "|",Space,Str "this\t|",Space,Str "is\t|",Space,Str "not\t|",Space,Str "a\t|",Space,Str "table\t|"] +,HorizontalRule +,Para [Str "The",Space,Str "End."]] diff --git a/tests/txt2tags.t2t b/tests/txt2tags.t2t new file mode 100644 index 000000000..e282498d0 --- /dev/null +++ b/tests/txt2tags.t2t @@ -0,0 +1,797 @@ +Txt2tags Markup Rules + + +%!includeconf: rules.conf + +This document describes all the details about each txt2tags mark. +The target audience are **experienced** users. You may find it +useful if you want to master the marks or solve a specific problem +about a mark. + +If you are new to txt2tags or just want to know which are the +available marks, please read the [Markup Demo MARKUPDEMO]. + +Note 1: This document is generated directly from the txt2tags +test-suite. All the rules mentioned here are 100% in sync with the +current program code. + +Note 2: A good practice is to consult [the sources rules.t2t] when +reading, to see how the texts were made. + +Table of Contents: + +%%TOC + +------------------------------------------------------------- + += Paragraph =[paragraph] + +%INCLUDED(t2t) starts here: ../../../test/marks/paragraph.t2t + + +%%% Syntax: Lines grouped together +A paragraph is composed by one or more lines. +A blank line (or a table, or a list) ends the +current paragraph. + +%%% Syntax: Leading and trailing spaces are ignored + Leading and trailing spaces are ignored. + +%%% Syntax: A comment don't close a paragraph +A comment line can be placed inside a paragraph. +% this comment will be ignored +It will not affect it. + +%%% Closing: EOF closes the open paragraph +The end of the file (EOF) closes the +currently open paragraph. + += Comment =[comment] + +%INCLUDED(t2t) starts here: ../../../test/marks/comment.t2t + + +%%% Syntax: The % character at the line beginning (column 1) +%glued with the % mark +% separated from the % mark +% very distant from the % mark +%%%%%%% lots of % marks +% a blank comment, used for vertical spacing: +% +% NOTE: what matters is the first % being at the line beginning, +% the rest of the line is just ignored. + +%%% Syntax: Area (block) +%%% +You're not seeing this. +%%% + +%%% Syntax: Area (block) with trailing spaces +%%% +You're not seeing this. +%%% + +%%% Invalid: The % in any other position + % not on the line beginning (at column 2) + +some text % half line comments are not allowed + + += Line =[line] + +%INCLUDED(t2t) starts here: ../../../test/marks/line.t2t + + +%%% Syntax: At least 20 chars of - = _ +-------------------- +==================== +____________________ +%%% Syntax: Any kind of mixing is allowed +%% Free mixing is allowed to make the line, +%% but the first char is the identifier for +%% the difference between separator ( - _ ) +%% and strong ( = ) lines. +=========----------- +-_-_-_-_-_-_-_-_-_-_ +=-=-=-=-=-=-=-=-=-=- +=------------------= +--------====-------- +%%% Syntax: Leading and/or trailing spaces are allowed + -------------------- +-------------------- + -------------------- +%%% Invalid: Less than 20 chars (but strike matches) +--------- +%%% Invalid: Strange chars (but strike matches) +--------- ---------- + +---------+---------- + +( -------------------- ) + += Inline =[inline] + +%INCLUDED(t2t) starts here: ../../../test/marks/inline.t2t + + +%%% Syntax: Marks are greedy and must be "glued" with contents +%% GLUED: The contents must be glued with the marks, no spaces +%% between them. Right after the opening mark there must be a +%% non-blank character, as well as right before the closing mark. +%% +%% GREEDY: If the contents boundary character is the same as +%% the mark character, it is considered contents, not mark. +%% So ""****bold****"" turns to ""<B>**bold**</B>"" in HTML. + +i) **b** //i// __u__ --s-- ``m`` ""r"" ''t'' +i) **bo** //it// __un__ --st-- ``mo`` ""ra"" ''tg'' +i) **bold** //ital// __undr__ --strk-- ``mono`` ""raw"" ''tggd'' +i) **bo ld** //it al// __un dr__ --st rk-- ``mo no`` ""r aw"" ''tg gd'' +i) **bo * ld** //it / al// __un _ dr__ --st - rk-- ``mo ` no`` ""r " aw"" ''tg ' gd'' +i) **bo **ld** //it //al// __un __dr__ --st --rk-- ``mo ``no`` ""r ""aw"" ''tg ''gd'' +i) **bo ** ld** //it // al// __un __ dr__ --st -- rk-- ``mo `` no`` ""r "" aw"" ''tg '' gd'' +i) ****bold**** ////ital//// ____undr____ ----strk---- ````mono```` """"raw"""" ''''tggd'''' +i) ***bold*** ///ital/// ___undr___ ---strk--- ```mono``` """raw""" '''tggd''' + +%%% Syntax: Repetition is greedy +%% When the mark character is repeated many times, +%% the contents are expanded to the largest possible. +%% Thats why they are greedy, the outer marks are +%% the ones used. + +i) ***** ///// _____ ----- ````` """"" ''''' +i) ****** ////// ______ ------ `````` """""" '''''' +i) ******* /////// _______ ------- ``````` """"""" ''''''' +i) ******** //////// ________ -------- ```````` """""""" '''''''' +i) ********* ///////// _________ --------- ````````` """"""""" ''''''''' +i) ********** ////////// __________ ---------- `````````` """""""""" '''''''''' + +%%% Invalid: No contents + +i) **** //// ____ ---- ```` """" '''' +i) ** ** // // __ __ -- -- `` `` "" "" '' '' + +%%% Invalid: Contents not "glued" with marks +%% Spaces between the marks and the contents in any side +%% invalidate the mark. + +i) ** bold** // ital// __ undr__ -- strk-- `` mono`` "" raw"" '' tggd'' +i) **bold ** //ital // __undr __ --strk -- ``mono `` ""raw "" ''tggd '' +i) ** bold ** // ital // __ undr __ -- strk -- `` mono `` "" raw "" '' tggd '' + += Link =[link] + +%INCLUDED(t2t) starts here: ../../../test/marks/link.t2t + + +%%% Syntax: E-mail +user@domain.com +user@domain.com. +user@domain.com. any text. +any text: user@domain.com. any text. +[label user@domain.com] +%%% Syntax: E-mail with form data +user@domain.com?subject=bla +user@domain.com?subject=bla. +user@domain.com?subject=bla, +user@domain.com?subject=bla&cc=otheruser@domain.com +user@domain.com?subject=bla&cc=otheruser@domain.com. +user@domain.com?subject=bla&cc=otheruser@domain.com, +[label user@domain.com?subject=bla&cc=otheruser@domain.com]. +[label user@domain.com?subject=bla&cc=otheruser@domain.com.]. +%%% Syntax: URL +http://www.domain.com +http://www.domain.com/dir/ +http://www.domain.com/dir/// +http://www.domain.com. +http://www.domain.com, +http://www.domain.com. any text. +http://www.domain.com, any text. +http://www.domain.com/dir/. any text. +any text: http://www.domain.com. any text. +any text: http://www.domain.com/dir/. any text. +any text: http://www.domain.com/dir/index.html. any text. +any text: http://www.domain.com/dir/index.html, any text. +%%% Syntax: URL with anchor +http://www.domain.com/dir/#anchor +http://www.domain.com/dir/index.html#anchor +http://www.domain.com/dir/index.html#anchor. +http://www.domain.com/dir/#anchor. any text. +http://www.domain.com/dir/index.html#anchor. any text. +any text: http://www.domain.com/dir/#anchor. any text. +any text: http://www.domain.com/dir/index.html#anchor. any text. +%%% Syntax: URL with form data +http://domain.com?a=a@a.a&b=a+b+c. +http://domain.com?a=a@a.a&b=a+b+c, +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@. +%%% Syntax: URL with form data and anchor +http://domain.com?a=a@a.a&b=a+b+c.#anchor +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 +%%% Syntax: URL with login data +http://user:password@domain.com/bla.html. +http://user:password@domain.com/dir/. +http://user:password@domain.com. +http://user:@domain.com. +http://user@domain.com. +%%% Syntax: URL with login, form and anchor +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 +%%% Syntax: URL with label +[label www.domain.com] +%%% Syntax: URL with label (trailing spaces are discarded, leading are maintained) +%TODO normalize this behavior +[ label www.domain.com] +[label www.domain.com] +%%% Syntax: URL with label, stressing +[anchor http://www.domain.com/dir/index.html#anchor.] +[login http://user:password@domain.com/bla.html] +[form http://www.domain.com/bla.cgi?a=a@a.a&b=a+b+c.] +[form & anchor http://www.domain.com/bla.cgi?a=a@a.a&b=a+b+c.#anchor] +[login & form http://user:password@domain.com/bla.cgi?a=a@a.a&b=a+b+c.] +%%% Syntax: Link with label for local files +[local link up ..] +[local link file bla.html] +[local link anchor #anchor] +[local link file/anchor bla.html#anchor] +[local link file/anchor bla.html#anchor.] +[local link img abc.gif] +%%% Syntax: Another link as a label +[www.fake.com www.domain.com] +%%% Syntax: URL with funny chars +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?a=/%22&b=+.@*_- +http://domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_-1%. +http://foo._user-9:pass!#$%&*()+word@domain.com:8080/~user/_st-r@a=n$g,e/index%20new.htm?a=/%22&b=+.@*_-#anchor_-1%. +%%% Test: Various per line +http://L1.com ! L2@www.com ! [L3 www.com] ! [L4 w@ww.com] ! www.L5.com +%%% Feature: Guessed link, adding protocol automatically +www.domain.com +www2.domain.com +ftp.domain.com +WWW.DOMAIN.COM +FTP.DOMAIN.COM +[label www.domain.com] +[label ftp.domain.com] +[label WWW.DOMAIN.COM] +[label FTP.DOMAIN.COM] +%%% Invalid: Trailing space on link +[label www.domain.com ] +%%% Invalid: Label with ] char (use postproc) +[label] www.domain.com] + += Image =[image] + +%INCLUDED(t2t) starts here: ../../../test/marks/image.t2t + + +%%% Syntax: Image name inside brackets: [img] +[img.png] + +%%% Syntax: Image pointing to a link: [[img] link] +[[img.png] http://txt2tags.org] + +%%% Align: Image position is preserved when inside paragraph +[img.png] Image at the line beginning. + +Image in the middle [img.png] of the line. + +Image at the line end. [img.png] + +%%% Align: Image alone with spaces around is aligned +[img.png] + [img.png] + [img.png] + +%%% Test: Two glued images with no spaces (left & right) +[img.png][img.png] + +%%% Test: Various per line +Images [img.png] mixed [img.png] with [img.png] text. + +Images glued together: [img.png][img.png][img.png]. + +%%% Invalid: Spaces inside are not allowed +[img.png ] + +[ img.png] + +[ img.png ] + +% Ignored as they change every time when run + += Numbered Title =[numtitle] + +%%% Syntax: Balanced equal signs (from 1 to 5) ++ Title Level 1 + +++ Title Level 2 ++ ++++ Title Level 3 +++ +++++ Title Level 4 ++++ ++++++ Title Level 5 +++++ +%%% Label: Between brackets, alphanumeric [A-Za-z0-9_-] ++ Title Level 1 +[lab_el-1] +++ Title Level 2 ++[lab_el-2] ++++ Title Level 3 +++[lab_el-3] +++++ Title Level 4 ++++[lab_el-4] ++++++ Title Level 5 +++++[lab_el-5] +%%% Syntax: Spaces around and/or inside are allowed (and ignored) + +++Title Level 3+++ + +++ Title Level 3 +++ + +++ Title Level 3 +++ ++++ Title Level 3 +++ ++++ Title Level 3 +++ + +++ Title Level 3 +++[lab_el-9] +%%% Invalid: Unbalanced equal signs + +Not Title + + ++Not Title+ + + +++Not Title++++ +%%% Invalid: Level deeper than 5 + ++++++Not Title 6++++++ + ++++++++Not Title 7+++++++ +%%% Invalid: Space between title and label ++Not Title+ [label1] +%%% Invalid: Space inside label ++Not Title+[ label ] +%%% Invalid: Strange chars inside label ++Not Title+[la/bel] + += Title =[title] + +%INCLUDED(t2t) starts here: ../../../test/marks/title.t2t + + +%%% Syntax: Balanced equal signs (from 1 to 5) += Title Level 1 = +== Title Level 2 == +=== Title Level 3 === +==== Title Level 4 ==== +===== Title Level 5 ===== +%%% Label: Between brackets, alphanumeric [A-Za-z0-9_-] += Title Level 1 =[lab_el-1] +== Title Level 2 ==[lab_el-2] +=== Title Level 3 ===[lab_el-3] +==== Title Level 4 ====[lab_el-4] +===== Title Level 5 =====[lab_el-5] +%%% Syntax: Spaces around and/or inside are allowed (and ignored) + ===Title Level 3=== + === Title Level 3 === + === Title Level 3 === +=== Title Level 3 === +=== Title Level 3 === + === Title Level 3 ===[lab_el-9] +%%% Invalid: Unbalanced equal signs + =Not Title + + ==Not Title= + + ===Not Title==== +%%% Invalid: Level deeper than 5 + ======Not Title 6====== + +=======Not Title 7======= +%%% Invalid: Space between title and label +=Not Title= [label1] +%%% Invalid: Space inside label +=Not Title=[ label ] +%%% Invalid: Strange chars inside label +=Not Title=[la/bel] + += Quote =[quote] + +%INCLUDED(t2t) starts here: ../../../test/marks/quote.t2t + + + To quote a paragraph, just prefix it by a TAB + character. All the lines of the paragraph must + begin with a TAB. +Any non-tabbed line closes the quote block. + +%%% Nesting: Creating deeper quotes + The number of leading TABs identifies the quote + block depth. This is quote level 1. + With two TABs, we are on the quote + level 2. + The more TABs, more deep is + the quote level. + There isn't a limit. + +%%% Nesting: Reverse nesting works + This quote starts at + level 4. + Then its depth is decreased. + Counting down, one by one. + Until the level 1. + +%%% Nesting: Random count + Unlike lists, any quote block is + independent, not part of a tree. + The TAB count don't need to be incremental + by one. + The nesting don't need + to follow any rule. + Quotes can be opened and closed + in any way. + You choose. + +%%% Nesting: When not supported + Some targets (as sgml) don't support the + nesting of quotes. There is only one quote + level. + In this case, no matter how much + TABs are used to define the quote + block, it always will be level 1. + +%%% Syntax: Spaces after TAB + Spaces AFTER the TAB character are allowed. + But be careful, it can be confusing. + +%%% Invalid: Spaces before TAB + Spaces BEFORE the TAB character + invalidate the mark. It's not quote. + +%%% Invalid: Paragraphs inside + Paragraph breaks inside a quote aren't + possible. + + This sample are two separated quoted + paragraphs, not a quote block with + two paragraphs inside. + +%%% Closing: EOF closes the open block + The end of the file (EOF) closes the + currently open quote block. + += Raw =[raw] + +%%% Syntax: A single line +""" A raw line. + +%%% Syntax: A single line with leading spaces +""" Another raw line, with leading spaces. + +%%% Syntax: Area (block) +""" +A raw area delimited + by lines with marks. +""" + +%%% Syntax: Area (block) with trailing spaces +""" +Trailing spaces and TABs after the area marks +are allowed, but not encouraged nor documented. +""" + +%%% Invalid: No space between mark and contents +"""Not a raw line, need one space after mark. + +%%% Invalid: Leading spaces on block marks + """ + Not a raw area. + The marks must be at the line beginning, + no leading spaces. + """ + +%%% Closing: EOF closes the open block +""" +The end of the file (EOF) closes +the currently open raw area. +""" + += Verbatim =[verbatim] + +%INCLUDED(t2t) starts here: ../../../test/marks/verbatim.t2t + + +%%% Syntax: A single line +``` A verbatim line. + +%%% Syntax: A single line with leading spaces +``` Another verbatim line, with leading spaces. + +%%% Syntax: Area (block) +``` +A verbatim area delimited + by lines with marks. +``` + +%%% Syntax: Area (block) with trailing spaces +``` +Trailing spaces and TABs after the area marks +are allowed, but not encouraged nor documented. +``` + +%%% Invalid: No space between mark and contents +```Not a verbatim line, need one space after mark. + +%%% Invalid: Leading spaces on block marks + ``` + Not a verbatim area. + The marks must be at the line beginning, + no leading spaces. + ``` + +%%% Closing: EOF closes the open block +``` +The end of the file (EOF) closes +the currently open verbatim area. +``` + += Definition List =[deflist] + +: Definition list + A list with terms +: Start term with colon + And its definition follows + + += Numbered List =[numlist] + +See [List #list], the same rules apply. + += List =[list] + +%INCLUDED(t2t) starts here: ../../../test/marks/list.t2t + + +%%% Items: Prefixed by hyphen +- Use the hyphen to prefix list items. +- There must be one space after the hyphen. +- The list is closed by two consecutive blank lines. + + +%%% Items: Free leading spacing (indentation) + - The list can be indented on the source document. + - You can use any number of spaces. + - The result will be the same. + + +%%% Items: Vertical spacing between items +- Let one blank line between the list items. + +- It will be maintained on the conversion. + +- Some targets don't support this behavior. + +- This one was separated by a line with blanks. + You can also put a blank line inside + + the item contents and it will be preserved. + + +%%% Items: Exactly ONE space after the hyphen +-This is not a list (no space) + +- This is not a list (more than one space) + +- This is not a list (a TAB instead the space) + + +%%% Items: Catchy cases +- - This is a list +- + This is a list +- : This is a list + + +%%% Nesting: Creating sublists +- This is the "mother" list first item. +- Here is the second, but inside this item, + - there is a sublist, with its own items. + - Note that the items of the same sublist + - must have the same indentation. + - And this can go on, opening sublists. + - Just add leading spaces before the + - hyphen and sublists will be opened. + - The two blank lines closes them all. + + +%%% Nesting: Free leading spacing (indentation) +- When nesting lists, the additional spaces are free. + - You can add just one, + - or many. + - What matters is to put more than the previous. + - But remember that the other items of the same list + - must use the same indentation. + + +%%% Nesting: Maximum depth +- There is not a depth limit, + - you can go deeper and deeper. + - But some targets may have restrictions. + - The LaTeX maximum is here, 4 levels. + + +%%% Nesting: Reverse doesn't work + - Reverse nesting doesn't work. + - Because a sublist *must* have a mother list. + - It's the list concept, not a txt2tags limitation. + - All this sublists will be bumped to mother lists. +- At level 1, like this one. + + +%%% Nesting: Going deeper and back + +%% When nesting back to an upper level, the previous sublist +%% is automatically closed. +- Level 1 + - Level 2 + - Level 3 + - Level 4 + - Level 3 -- (closed Level 4) + - Level 2 -- (closed Level 3) +- Level 1 -- (closed Level 2) + + +%% More than one list can be closed when nesting back. +- Level 1 + - Level 2 + - Level 3 + - Level 4 +- Level 1 -- (closed Level 4, Level 3 and Level 2) + + +%%% Nesting: Vertical spacing between lists +- Level 1 + + - Level 2 -- blank BEFORE and AFTER (in) + + - Level 3 +% comment lines are NOT considered blank lines + - Level 4 +% comment lines are NOT considered blank lines + - Level 3 + + - Level 2 -- blank BEFORE and AFTER (out) + +- Level 1 + + - Level 2 -- blank BEFORE (spaces) and AFTER (TAB) + + - Level 3 + + +%%% Nesting: Messing up +%% Be careful when going back on the nesting, +%% it must be on a valid level! If not, it will +%% be bumped up to the previous valid level. +- Level 1 + - Level 2 + - Level 3 + - Level 4 + - Level 3.5 ??? + - Level 3 + - Level 2.5 ??? + - Level 2 + - Level 1.5 ??? +- Level 1 + + +%%% Closing: Two (not so) empty lines +- This list is closed by a line with spaces and other with TABs + + +- This list is NOT closed by two comment lines +% comment lines are NOT considered blank lines +% comment lines are NOT considered blank lines +- This list is closed by a line with spaces and TAB, +- then a comment line, then an empty line. + +% comment lines are NOT considered blank lines + +%%% Closing: Empty item closes current (sub)list + +%% The two blank lines closes ALL the lists. +%% To close just the current, use an empty item. +- Level 1 + - Level 2 + - Level 3 + - + Level 2 + - + Level 1 +- + +%% The empty item can have trailing blanks. +- Empty item with trailing spaces. +- + +- Empty item with trailing TAB. +- + +%%% Closing: EOF closes the lists +- If the end of the file (EOF) is hit, + - all the currently opened list are closed, + - just like when using the two blank lines. + + += Table =[table] + +%INCLUDED(t2t) starts here: ../../../test/marks/table.t2t + +%%% Syntax: Lines starting with a pipe | +| Cell 1 + +%%% Syntax: Extra pipes separate cells +| Cell 1 | Cell 2 | Cell 3 + +%%% Syntax: With a trailing pipe, make border +| Cell 1 | Cell 2 | Cell 3 | + +%%% Syntax: Table lines starting with double pipe are heading +|| Cell 1 | Cell 2 | Cell 3 | + +%%% Align: Spaces before the leading pipe centralize the table + | Cell 1 | Cell 2 | Cell 3 | + +%%% Align: Spaces inside the cell denote its alignment + || Heading | Heading | Heading | +% comments don't close an opened table + | <- | -- | -> | + | -- | -- | -- | + | -> | -- | <- | + +%%% Span: Column span is defined by extra pipes at cell closing + || 1 | 2 | 3+4 || + | 1 | 2 | 3 | 4 | + | 1+2+3 ||| 4 | + | 1 | 2+3 || 4 | + | 1+2+3+4 |||| + +%%% Test: Empty cells are placed as expected + | 0 | 1 | 2 | | + | 4 | 5 | | 7 | + | 8 | | A | B | + | | D | E | F | + +%%% Test: Lines with different number of cells + | 1 | + | 1 | 2 | + | 1 | 2 | 3 | + | 1 | 2 | 3 | 4 | + | 1 | 2 | 3 | 4 | 5 | + +%%% Test: Empty cells + Span + Messy cell number = Fun! + | Jan | + | Fev || + | Mar ||| + | Apr |||| + | May ||||| + | 20% | 40% | 60% | 80% | 100% | + + | | | / | | | + | | / / / / / ||| | + | / / / / / / / / / ||||| + | | o | | o | | + | | | . | | | + | | = = = = ||| | + + | 01 | 02 | | | 05 | | 07 | | + | | | 11 | | 13 | | | 16 | + | 17 | | 19 | 20 | | | 23 | | + | 25 | 26 | | | 29 | 30 | | 32 | + | | | 35 | | 37 | | 39 | 40 | + +%%% Test: Lots of cells at the same line +| 0 | 1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 | A | B | C | D | E | F | 0 | 1 | 2 | 3 | 4 | 5 | 6 | 7 | 8 | 9 | A | B | C | D | E | F | + +%%% Test: Empty lines +| | +| | +| | + +%%% Invalid: There must be at least one space around the pipe +|this|is|not|a|table| + +|this| is| not| a| table| + +|this |is |not |a |table | + +%%% Invalid: You must use spaces, not TABs +| this | is | not | a | table | + +------------------------------------------------------------ + +The End. diff --git a/tests/writer.latex b/tests/writer.latex index bf08c7111..5428e9ad7 100644 --- a/tests/writer.latex +++ b/tests/writer.latex @@ -709,20 +709,20 @@ Ellipses\ldots{}and\ldots{}and\ldots{}. \item \cite[22-23]{smith.1899} \item - $2+2=4$ + \(2+2=4\) \item - $x \in y$ + \(x \in y\) \item - $\alpha \wedge \omega$ + \(\alpha \wedge \omega\) \item - $223$ + \(223\) \item - $p$-Tree + \(p\)-Tree \item Here's some display math: \[\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}\] \item - Here's one that has a line break in it: $\alpha + \omega \times x^2$. + Here's one that has a line break in it: \(\alpha + \omega \times x^2\). \end{itemize} These shouldn't be math: diff --git a/tests/writer.markdown b/tests/writer.markdown index 9974d27e0..ad97b15ef 100644 --- a/tests/writer.markdown +++ b/tests/writer.markdown @@ -9,7 +9,7 @@ title: Pandoc Test Suite This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite. -* * * * * +------------------------------------------------------------------------------ Headers ======= @@ -38,7 +38,7 @@ Level 2 with no blank line -* * * * * +------------------------------------------------------------------------------ Paragraphs ========== @@ -54,7 +54,7 @@ Here’s one with a bullet. \* criminey. There should be a hard line break\ here. -* * * * * +------------------------------------------------------------------------------ Block Quotes ============ @@ -84,7 +84,7 @@ This should not be a block quote: 2 \> 1. And a following paragraph. -* * * * * +------------------------------------------------------------------------------ Code Blocks =========== @@ -105,7 +105,7 @@ And: These should not be escaped: \$ \\ \> \[ \{ -* * * * * +------------------------------------------------------------------------------ Lists ===== @@ -268,7 +268,7 @@ M.A. 2007 B. Williams -* * * * * +------------------------------------------------------------------------------ Definition Lists ================ @@ -277,8 +277,10 @@ Tight using spaces: apple : red fruit + orange : orange fruit + banana : yellow fruit @@ -286,30 +288,37 @@ Tight using tabs: apple : red fruit + orange : orange fruit + banana : yellow fruit Loose: apple + : red fruit orange + : orange fruit banana + : yellow fruit Multiple blocks with italics: *apple* + : red fruit contains seeds, crisp, pleasant to taste *orange* + : orange fruit { orange code block } @@ -321,6 +330,7 @@ Multiple definitions, tight: apple : red fruit : computer + orange : orange fruit : bank @@ -328,11 +338,13 @@ orange Multiple definitions, loose: apple + : red fruit : computer orange + : orange fruit : bank @@ -340,11 +352,13 @@ orange Blank line after term, indented marker, alternate markers: apple + : red fruit : computer orange + : orange fruit 1. sublist @@ -465,7 +479,7 @@ Hr’s: <hr class="foo" id="bar" /> <hr class="foo" id="bar"> -* * * * * +------------------------------------------------------------------------------ Inline Markup ============= @@ -495,7 +509,7 @@ Subscripts: H~2~O, H~23~O, H~many of them~O. These should not be superscripts or subscripts, because of the unescaped spaces: a\^b c\^d, a\~b c\~d. -* * * * * +------------------------------------------------------------------------------ Smart quotes, ellipses, dashes ============================== @@ -517,7 +531,7 @@ Dashes between numbers: 5–7, 255–66, 1987–1999. Ellipses…and…and…. -* * * * * +------------------------------------------------------------------------------ LaTeX ===== @@ -548,7 +562,7 @@ Dog & 2 \\ Cat & 1 \\ \hline \end{tabular} -* * * * * +------------------------------------------------------------------------------ Special Characters ================== @@ -603,7 +617,7 @@ Plus: + Minus: - -* * * * * +------------------------------------------------------------------------------ Links ===== @@ -685,7 +699,7 @@ Auto-links should not occur here: `<http://example.com/>` or here: <http://example.com/> -* * * * * +------------------------------------------------------------------------------ Images ====== @@ -696,7 +710,7 @@ From “Voyage dans la Lune” by Georges Melies (1902): Here is a movie  icon. -* * * * * +------------------------------------------------------------------------------ Footnotes ========= diff --git a/tests/writer.opml b/tests/writer.opml index 7c7ff01c9..54be4b671 100644 --- a/tests/writer.opml +++ b/tests/writer.opml @@ -21,14 +21,14 @@ <outline text="Level 3" _note="with no blank line "> </outline> </outline> - <outline text="Level 2" _note="with no blank line * * * * *"> + <outline text="Level 2" _note="with no blank line ------------------------------------------------------------------------"> </outline> </outline> -<outline text="Paragraphs" _note="Here’s a regular paragraph. In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item. Here’s one with a bullet. \* criminey. There should be a hard line break\ here. * * * * *"> +<outline text="Paragraphs" _note="Here’s a regular paragraph. In Markdown 1.0.0 and earlier. Version 8. This line turns into a list item. Because a hard-wrapped line in the middle of a paragraph looked like a list item. Here’s one with a bullet. \* criminey. There should be a hard line break\ here. ------------------------------------------------------------------------"> </outline> -<outline text="Block Quotes" _note="E-mail style: > This is a block quote. It is pretty short. > Code in a block quote: > > sub status { > print "working"; > } > > A list: > > 1. item one > 2. item two > > Nested block quotes: > > > nested > > > nested This should not be a block quote: 2 \> 1. And a following paragraph. * * * * *"> +<outline text="Block Quotes" _note="E-mail style: > This is a block quote. It is pretty short. > Code in a block quote: > > sub status { > print "working"; > } > > A list: > > 1. item one > 2. item two > > Nested block quotes: > > > nested > > > nested This should not be a block quote: 2 \> 1. And a following paragraph. ------------------------------------------------------------------------"> </outline> -<outline text="Code Blocks" _note="Code: ---- (should be four hyphens) sub status { print "working"; } this code block is indented by one tab And: this code block is indented by two tabs These should not be escaped: \$ \\ \> \[ \{ * * * * *"> +<outline text="Code Blocks" _note="Code: ---- (should be four hyphens) sub status { print "working"; } this code block is indented by one tab And: this code block is indented by two tabs These should not be escaped: \$ \\ \> \[ \{ ------------------------------------------------------------------------"> </outline> <outline text="Lists"> <outline text="Unordered" _note="Asterisks tight: - asterisk 1 - asterisk 2 - asterisk 3 Asterisks loose: - asterisk 1 - asterisk 2 - asterisk 3 Pluses tight: - Plus 1 - Plus 2 - Plus 3 Pluses loose: - Plus 1 - Plus 2 - Plus 3 Minuses tight: - Minus 1 - Minus 2 - Minus 3 Minuses loose: - Minus 1 - Minus 2 - Minus 3 "> @@ -39,20 +39,20 @@ </outline> <outline text="Tabs and spaces" _note="- this is a list item indented with tabs - this is a list item indented with spaces - this is an example list item indented with tabs - this is an example list item indented with spaces "> </outline> - <outline text="Fancy list markers" _note="(2) begins with 2 (3) and now 3 with a continuation iv. sublist with roman numerals, starting with 4 v. more items (A) a subsublist (B) a subsublist Nesting: A. Upper Alpha I. Upper Roman. (6) Decimal start with 6 c) Lower alpha with paren Autonumbering: 1. Autonumber. 2. More. 1. Nested. Should not be a list item: M.A. 2007 B. Williams * * * * *"> + <outline text="Fancy list markers" _note="(2) begins with 2 (3) and now 3 with a continuation iv. sublist with roman numerals, starting with 4 v. more items (A) a subsublist (B) a subsublist Nesting: A. Upper Alpha I. Upper Roman. (6) Decimal start with 6 c) Lower alpha with paren Autonumbering: 1. Autonumber. 2. More. 1. Nested. Should not be a list item: M.A. 2007 B. Williams ------------------------------------------------------------------------"> </outline> </outline> -<outline text="Definition Lists" _note="Tight using spaces: apple : red fruit orange : orange fruit banana : yellow fruit Tight using tabs: apple : red fruit orange : orange fruit banana : yellow fruit Loose: apple : red fruit orange : orange fruit banana : yellow fruit Multiple blocks with italics: *apple* : red fruit contains seeds, crisp, pleasant to taste *orange* : orange fruit { orange code block } > orange block quote Multiple definitions, tight: apple : red fruit : computer orange : orange fruit : bank Multiple definitions, loose: apple : red fruit : computer orange : orange fruit : bank Blank line after term, indented marker, alternate markers: apple : red fruit : computer orange : orange fruit 1. sublist 2. sublist "> +<outline text="Definition Lists" _note="Tight using spaces: apple : red fruit orange : orange fruit banana : yellow fruit Tight using tabs: apple : red fruit orange : orange fruit banana : yellow fruit Loose: apple : red fruit orange : orange fruit banana : yellow fruit Multiple blocks with italics: *apple* : red fruit contains seeds, crisp, pleasant to taste *orange* : orange fruit { orange code block } > orange block quote Multiple definitions, tight: apple : red fruit : computer orange : orange fruit : bank Multiple definitions, loose: apple : red fruit : computer orange : orange fruit : bank Blank line after term, indented marker, alternate markers: apple : red fruit : computer orange : orange fruit 1. sublist 2. sublist "> </outline> -<outline text="HTML Blocks" _note="Simple block on one line: <div> foo </div> And nested without indentation: <div> <div> <div> foo </div> </div> <div> bar </div> </div> Interpreted markdown in a table: <table> <tr> <td> This is *emphasized* </td> <td> And this is **strong** </td> </tr> </table> <script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> Here’s a simple block: <div> foo </div> This should be a code block, though: <div> foo </div> As should this: <div>foo</div> Now, nested: <div> <div> <div> foo </div> </div> </div> This should just be an HTML comment: <!-- Comment --> Multiline: <!-- Blah Blah --> <!-- This is another comment. --> Code block: <!-- Comment --> Just plain comment, with trailing spaces on the line: <!-- foo --> Code: <hr /> Hr’s: <hr> <hr /> <hr /> <hr> <hr /> <hr /> <hr class="foo" id="bar" /> <hr class="foo" id="bar" /> <hr class="foo" id="bar"> * * * * *"> +<outline text="HTML Blocks" _note="Simple block on one line: <div> foo </div> And nested without indentation: <div> <div> <div> foo </div> </div> <div> bar </div> </div> Interpreted markdown in a table: <table> <tr> <td> This is *emphasized* </td> <td> And this is **strong** </td> </tr> </table> <script type="text/javascript">document.write('This *should not* be interpreted as markdown');</script> Here’s a simple block: <div> foo </div> This should be a code block, though: <div> foo </div> As should this: <div>foo</div> Now, nested: <div> <div> <div> foo </div> </div> </div> This should just be an HTML comment: <!-- Comment --> Multiline: <!-- Blah Blah --> <!-- This is another comment. --> Code block: <!-- Comment --> Just plain comment, with trailing spaces on the line: <!-- foo --> Code: <hr /> Hr’s: <hr> <hr /> <hr /> <hr> <hr /> <hr /> <hr class="foo" id="bar" /> <hr class="foo" id="bar" /> <hr class="foo" id="bar"> ------------------------------------------------------------------------"> </outline> -<outline text="Inline Markup" _note="This is *emphasized*, and so *is this*. This is **strong**, and so **is this**. An *[emphasized link](/url)*. ***This is strong and em.*** So is ***this*** word. ***This is strong and em.*** So is ***this*** word. This is code: `>`, `$`, `\`, `\$`, `<html>`. ~~This is *strikeout*.~~ Superscripts: a^bc^d a^*hello*^ a^hello there^. Subscripts: H~2~O, H~23~O, H~many of them~O. These should not be superscripts or subscripts, because of the unescaped spaces: a\^b c\^d, a\~b c\~d. * * * * *"> +<outline text="Inline Markup" _note="This is *emphasized*, and so *is this*. This is **strong**, and so **is this**. An *[emphasized link](/url)*. ***This is strong and em.*** So is ***this*** word. ***This is strong and em.*** So is ***this*** word. This is code: `>`, `$`, `\`, `\$`, `<html>`. ~~This is *strikeout*.~~ Superscripts: a^bc^d a^*hello*^ a^hello there^. Subscripts: H~2~O, H~23~O, H~many of them~O. These should not be superscripts or subscripts, because of the unescaped spaces: a\^b c\^d, a\~b c\~d. ------------------------------------------------------------------------"> </outline> -<outline text="Smart quotes, ellipses, dashes" _note="“Hello,” said the spider. “‘Shelob’ is my name.” ‘A’, ‘B’, and ‘C’ are letters. ‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’ ‘He said, “I want to go.”’ Were you alive in the 70’s? Here is some quoted ‘`code`’ and a “[quoted link](http://example.com/?foo=1&bar=2)”. Some dashes: one—two — three—four — five. Dashes between numbers: 5–7, 255–66, 1987–1999. Ellipses…and…and…. * * * * *"> +<outline text="Smart quotes, ellipses, dashes" _note="“Hello,” said the spider. “‘Shelob’ is my name.” ‘A’, ‘B’, and ‘C’ are letters. ‘Oak,’ ‘elm,’ and ‘beech’ are names of trees. So is ‘pine.’ ‘He said, “I want to go.”’ Were you alive in the 70’s? Here is some quoted ‘`code`’ and a “[quoted link](http://example.com/?foo=1&bar=2)”. Some dashes: one—two — three—four — five. Dashes between numbers: 5–7, 255–66, 1987–1999. Ellipses…and…and…. ------------------------------------------------------------------------"> </outline> -<outline text="LaTeX" _note="- \cite[22-23]{smith.1899} - $2+2=4$ - $x \in y$ - $\alpha \wedge \omega$ - $223$ - $p$-Tree - Here’s some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ - Here’s one that has a line break in it: $\alpha + \omega \times x^2$. These shouldn’t be math: - To get the famous equation, write `$e = mc^2$`. - \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is emphasized.) - Shoes (\$20) and socks (\$5). - Escaped `$`: \$73 *this should be emphasized* 23\$. Here’s a LaTeX table: \begin{tabular}{|l|l|}\hline Animal & Number \\ \hline Dog & 2 \\ Cat & 1 \\ \hline \end{tabular} * * * * *"> +<outline text="LaTeX" _note="- \cite[22-23]{smith.1899} - $2+2=4$ - $x \in y$ - $\alpha \wedge \omega$ - $223$ - $p$-Tree - Here’s some display math: $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ - Here’s one that has a line break in it: $\alpha + \omega \times x^2$. These shouldn’t be math: - To get the famous equation, write `$e = mc^2$`. - \$22,000 is a *lot* of money. So is \$34,000. (It worked if “lot” is emphasized.) - Shoes (\$20) and socks (\$5). - Escaped `$`: \$73 *this should be emphasized* 23\$. Here’s a LaTeX table: \begin{tabular}{|l|l|}\hline Animal & Number \\ \hline Dog & 2 \\ Cat & 1 \\ \hline \end{tabular} ------------------------------------------------------------------------"> </outline> -<outline text="Special Characters" _note="Here is some unicode: - I hat: Î - o umlaut: ö - section: § - set membership: ∈ - copyright: © AT&T has an ampersand in their name. AT&T is another way to write it. This & that. 4 \< 5. 6 \> 5. Backslash: \\ Backtick: \` Asterisk: \* Underscore: \_ Left brace: { Right brace: } Left bracket: [ Right bracket: ] Left paren: ( Right paren: ) Greater-than: \> Hash: \# Period: . Bang: ! Plus: + Minus: - * * * * *"> +<outline text="Special Characters" _note="Here is some unicode: - I hat: Î - o umlaut: ö - section: § - set membership: ∈ - copyright: © AT&T has an ampersand in their name. AT&T is another way to write it. This & that. 4 \< 5. 6 \> 5. Backslash: \\ Backtick: \` Asterisk: \* Underscore: \_ Left brace: { Right brace: } Left bracket: [ Right bracket: ] Left paren: ( Right paren: ) Greater-than: \> Hash: \# Period: . Bang: ! Plus: + Minus: - ------------------------------------------------------------------------"> </outline> <outline text="Links"> <outline text="Explicit" _note="Just a [URL](/url/). [URL and title](/url/ "title"). [URL and title](/url/ "title preceded by two spaces"). [URL and title](/url/ "title preceded by a tab"). [URL and title](/url/ "title with "quotes" in it") [URL and title](/url/ "title with single quotes") [with\_underscore](/url/with_underscore) [Email link](mailto:nobody@nowhere.net) [Empty](). "> @@ -61,10 +61,10 @@ </outline> <outline text="With ampersands" _note="Here’s a [link with an ampersand in the URL](http://example.com/?foo=1&bar=2). Here’s a link with an amersand in the link text: [AT&T](http://att.com/ "AT&T"). Here’s an [inline link](/script?foo=1&bar=2). Here’s an [inline link in pointy braces](/script?foo=1&bar=2). "> </outline> - <outline text="Autolinks" _note="With an ampersand: <http://example.com/?foo=1&bar=2> - In a list? - <http://example.com/> - It should. An e-mail address: <nobody@nowhere.net> > Blockquoted: <http://example.com/> Auto-links should not occur here: `<http://example.com/>` or here: <http://example.com/> * * * * *"> + <outline text="Autolinks" _note="With an ampersand: <http://example.com/?foo=1&bar=2> - In a list? - <http://example.com/> - It should. An e-mail address: <nobody@nowhere.net> > Blockquoted: <http://example.com/> Auto-links should not occur here: `<http://example.com/>` or here: <http://example.com/> ------------------------------------------------------------------------"> </outline> </outline> -<outline text="Images" _note="From “Voyage dans la Lune” by Georges Melies (1902):  Here is a movie  icon. * * * * *"> +<outline text="Images" _note="From “Voyage dans la Lune” by Georges Melies (1902):  Here is a movie  icon. ------------------------------------------------------------------------"> </outline> <outline text="Footnotes" _note="Here is a footnote reference,[^1] and another.[^2] This should *not* be a footnote reference, because it contains a space.[\^my note] Here is an inline note.[^3] > Notes can go in quotes.[^4] 1. And in list items.[^5] This paragraph should not be part of the note, as it is not indented. [^1]: Here is the footnote. It can go anywhere after the footnote reference. It need not be placed at the end of the document. [^2]: Here’s the long note. This one contains multiple blocks. Subsequent blocks are indented to show that they belong to the footnote (as with list items). { <code> } If you want, you can indent every line, but you can also be lazy and just indent the first line of each block. [^3]: This is *easier* to type. Inline notes may contain [links](http://google.com) and `]` verbatim characters, as well as [bracketed text]. [^4]: In quote. [^5]: In list. "> </outline> diff --git a/tests/writer.plain b/tests/writer.plain index 60e7bb329..bd1a06998 100644 --- a/tests/writer.plain +++ b/tests/writer.plain @@ -5,39 +5,43 @@ July 17, 2006 This is a set of tests for pandoc. Most of them are adapted from John Gruber’s markdown test suite. -* * * * * +------------------------------------------------------------------------------ + + Headers -======= + Level 2 with an embedded link ------------------------------ -Level 3 with emphasis +Level 3 with _emphasis_ Level 4 Level 5 + + Level 1 -======= -Level 2 with emphasis ---------------------- + +Level 2 with _emphasis_ Level 3 with no blank line + Level 2 -------- with no blank line -* * * * * +------------------------------------------------------------------------------ + + Paragraphs -========== + Here’s a regular paragraph. @@ -47,13 +51,15 @@ item. Here’s one with a bullet. * criminey. -There should be a hard line break +There should be a hard line break here. -* * * * * +------------------------------------------------------------------------------ + + Block Quotes -============ + E-mail style: @@ -80,10 +86,12 @@ This should not be a block quote: 2 > 1. And a following paragraph. -* * * * * +------------------------------------------------------------------------------ + + Code Blocks -=========== + Code: @@ -101,13 +109,14 @@ And: These should not be escaped: \$ \\ \> \[ \{ -* * * * * +------------------------------------------------------------------------------ + + Lists -===== + Unordered ---------- Asterisks tight: @@ -151,8 +160,8 @@ Minuses loose: - Minus 3 + Ordered -------- Tight: @@ -192,8 +201,8 @@ Multiple paragraphs: 3. Item 3. + Nested ------- - Tab - Tab @@ -221,8 +230,8 @@ Same thing but with paragraphs: 3. Third + Tabs and spaces ---------------- - this is a list item indented with tabs @@ -232,8 +241,8 @@ Tabs and spaces - this is an example list item indented with spaces + Fancy list markers ------------------- (2) begins with 2 (3) and now 3 @@ -264,17 +273,21 @@ M.A. 2007 B. Williams -* * * * * +------------------------------------------------------------------------------ + + Definition Lists -================ + Tight using spaces: apple red fruit + orange orange fruit + banana yellow fruit @@ -282,30 +295,37 @@ Tight using tabs: apple red fruit + orange orange fruit + banana yellow fruit Loose: apple + red fruit orange + orange fruit banana + yellow fruit Multiple blocks with italics: -apple +_apple_ + red fruit contains seeds, crisp, pleasant to taste -orange +_orange_ + orange fruit { orange code block } @@ -317,6 +337,7 @@ Multiple definitions, tight: apple red fruit computer + orange orange fruit bank @@ -324,11 +345,13 @@ orange Multiple definitions, loose: apple + red fruit computer orange + orange fruit bank @@ -336,18 +359,22 @@ orange Blank line after term, indented marker, alternate markers: apple + red fruit computer orange + orange fruit 1. sublist 2. sublist + + HTML Blocks -=========== + Simple block on one line: @@ -361,8 +388,8 @@ bar Interpreted markdown in a table: -This is emphasized -And this is strong +This is _emphasized_ +And this is STRONG Here’s a simple block: foo @@ -397,40 +424,44 @@ Code: Hr’s: -* * * * * +------------------------------------------------------------------------------ + + Inline Markup -============= -This is emphasized, and so is this. -This is strong, and so is this. +This is _emphasized_, and so _is this_. + +This is STRONG, and so IS THIS. -An emphasized link. +An _emphasized link_. -This is strong and em. +_THIS IS STRONG AND EM._ -So is this word. +So is _THIS_ word. -This is strong and em. +_THIS IS STRONG AND EM._ -So is this word. +So is _THIS_ word. This is code: >, $, \, \$, <html>. -This is strikeout. +~~This is _strikeout_.~~ -Superscripts: abcd ahello ahello there. +Superscripts: a^bc^d a^_hello_^ a^hello there^. -Subscripts: H2O, H23O, Hmany of themO. +Subscripts: H~2~O, H~23~O, H~many of them~O. These should not be superscripts or subscripts, because of the unescaped spaces: a^b c^d, a~b c~d. -* * * * * +------------------------------------------------------------------------------ + + Smart quotes, ellipses, dashes -============================== + “Hello,” said the spider. “‘Shelob’ is my name.” @@ -448,35 +479,39 @@ Dashes between numbers: 5–7, 255–66, 1987–1999. Ellipses…and…and…. -* * * * * +------------------------------------------------------------------------------ + + LaTeX -===== -- -- 2+2=4 -- x \in y -- \alpha \wedge \omega + +- \cite[22-23]{smith.1899} +- 2 + 2 = 4 +- x ∈ y +- α ∧ ω - 223 - p-Tree - Here’s some display math: - \frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h} -- Here’s one that has a line break in it: \alpha + \omega \times x^2. + $$\frac{d}{dx}f(x)=\lim_{h\to 0}\frac{f(x+h)-f(x)}{h}$$ +- Here’s one that has a line break in it: α + ω × x^2^. These shouldn’t be math: - To get the famous equation, write $e = mc^2$. -- $22,000 is a lot of money. So is $34,000. (It worked if “lot” is +- $22,000 is a _lot_ of money. So is $34,000. (It worked if “lot” is emphasized.) - Shoes ($20) and socks ($5). -- Escaped $: $73 this should be emphasized 23$. +- Escaped $: $73 _this should be emphasized_ 23$. Here’s a LaTeX table: -* * * * * +------------------------------------------------------------------------------ + + Special Characters -================== + Here is some unicode: @@ -528,13 +563,14 @@ Plus: + Minus: - -* * * * * +------------------------------------------------------------------------------ + + Links -===== + Explicit --------- Just a URL. @@ -554,8 +590,8 @@ Email link Empty. + Reference ---------- Foo bar. @@ -581,8 +617,8 @@ Foo bar. Foo biz. + With ampersands ---------------- Here’s a link with an ampersand in the URL. @@ -592,8 +628,8 @@ Here’s an inline link. Here’s an inline link in pointy braces. + Autolinks ---------- With an ampersand: http://example.com/?foo=1&bar=2 @@ -609,10 +645,12 @@ Auto-links should not occur here: <http://example.com/> or here: <http://example.com/> -* * * * * +------------------------------------------------------------------------------ + + Images -====== + From “Voyage dans la Lune” by Georges Melies (1902): @@ -620,37 +658,39 @@ From “Voyage dans la Lune” by Georges Melies (1902): Here is a movie [movie] icon. -* * * * * +------------------------------------------------------------------------------ + + Footnotes -========= -Here is a footnote reference,[^1] and another.[^2] This should not be a + +Here is a footnote reference,[1] and another.[2] This should _not_ be a footnote reference, because it contains a space.[^my note] Here is an inline -note.[^3] +note.[3] - Notes can go in quotes.[^4] + Notes can go in quotes.[4] -1. And in list items.[^5] +1. And in list items.[5] This paragraph should not be part of the note, as it is not indented. -[^1]: Here is the footnote. It can go anywhere after the footnote reference. - It need not be placed at the end of the document. +[1] Here is the footnote. It can go anywhere after the footnote reference. It +need not be placed at the end of the document. -[^2]: Here’s the long note. This one contains multiple blocks. +[2] Here’s the long note. This one contains multiple blocks. - Subsequent blocks are indented to show that they belong to the footnote - (as with list items). +Subsequent blocks are indented to show that they belong to the footnote (as +with list items). - { <code> } + { <code> } - If you want, you can indent every line, but you can also be lazy and just - indent the first line of each block. +If you want, you can indent every line, but you can also be lazy and just +indent the first line of each block. -[^3]: This is easier to type. Inline notes may contain links and ] verbatim - characters, as well as [bracketed text]. +[3] This is _easier_ to type. Inline notes may contain links and ] verbatim +characters, as well as [bracketed text]. -[^4]: In quote. +[4] In quote. -[^5]: In list. +[5] In list. diff --git a/tests/writer.rtf b/tests/writer.rtf index 954d95cc4..527906e4d 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 ffd8ffe000104a46494600010101007800780000ffdb00430006040506050406060506070706080a100a0a09090a140e0f0c1017141818171416161a1d251f1a1b231c1616202c20232627292a29191f2d302d283025282928ffdb0043010707070a080a130a0a13281a161a2828282828282828282828282828282828282828282828282828282828282828282828282828282828282828282828282828ffc000110800fa00fa03011100021101031101ffc4001c0000000701010000000000000000000000010203040506070008ffc4003e100002010303020404040502050500030001020300041105122106311322415107617181143291a1234252b1c115f016336272d1082443e1f1265382ffc40017010101010100000000000000000000000000010204ffc4001b11010101010003010000000000000000000001110212213141ffda000c03010002110311003f00dadd18a10a704f6a95ccc57e37750782b0d8d9ea0cd32e7c5446e07e9f4ad723119a7b89e61e348f260719278aad613cbb640002938c76a182b264fc87bd13009c0c019c76e3d68a072e1cf6f4cd502d330c28269a61bb39c923923d4fad44c08dccb95cfd28b8280769ee08a263891e1808739e4f1d8d149392172cc714050dbb9fde8960ed8c60b79b1ed44103b05c331dbdb1dc5026ac1946d20ff8140aa631c773ec738a0346a003bf93e9cf02801895e7b9a01886796c923bd0090a06393c76a0142003ce3d86680d8dd9392303f5341ccc1b3cf7a2c812c37e4923d381429757013209fa511c18146c9247a0f6a007900c0c671c6280854e086c673eb45c27c038fd68aedff2fda836ef881f136f25d5e6b7d1262964aa02b03f98fbf153131935edcc97576f35c33349212cc4f39f7ab26186dfce5b200f73451f7600dcb8cf27e7400c0b291914046c9e0718fde81371b8e7273f4ef4007691919240e714097f31f376e7b5008caee27807b0f5a02c8e1b3c6d27d33cd0201d839523144d1a149ae084b78da47638211771fd050d582c3a0faab5119b6d12f8ab1c06788a0fd4e2ac356fd1fe08754ddccaba849696309e598c9e2103fed1dcfdeadc44fea5ff00a7f956366d375e492403ca935bedcf1eea4ff6ac68a55efc1beb3b552574f8e7009ff933a927ec715bc82b3a8f4d6bba5ca1352d22fe061cf9a0383f71dea5119cc6c0baed3eaac0f1fad40897dcc3d81f7a052366c1007df3400f21edefc5008c28f30c9c5170ee4fc37830086395250a7c66770c18e78da31c0c63de8609b41f7c515c5172a30c3b76344a3e377cb2339cf7a242aea89808cce368272b8c1a2e107c672a49f5c1a181c9c7ae7da8a2119e7b1f5068099ffa68258a132062d8f9e0f34059502b61bf2824e681bb297ced2a71efda80f19c47b9c77fdbe74057c13e539cf3c1a0eeeb9c73f33405ddb4f18249c1e28062b79ae242902024465b9214614649e7bd0362a7249eddc513456e5720f38f5a1a98e96e95d6baa6ebc2d1ad1e65521649bb469f563534d6d7d31f04347d2a2fc5f535db6a0e83718906c887cbbe5a9a8bef44dce9f731ca9a2e89169d6d6f2184b1455dc07b11dcfeb4d16f119c649a681285b03d3e5500f87820ff006a0e098191de80ac9b8904647b55d11da9681a56a31f87a869f6970b8ffe4883629a289aefc16e92d441682da5b098f21ed9f033f353914d19b751fc08d66cc16d12fe2bf45ec92ff0df1fdbfb559ec667aff4eeb1a04db359d3ae6d40eccebe53f46ec7f5ab82263da7dcf3eb5174e5181076918c7de869503232491ee4515c1803824f03b51287f30e0e7d803449494832c157278a2e8c71fcb9f9d144639236824d01e142efb1768cfb9c7ef40512a818de78ff00a682518e7cc30ab9e00a02cce9953247bd41e467191ed9a04205ee99da4e4e3d283a524b0427b5026c18a8e082067db8341ce0e39ed409b6502907391edda80f2dfdc496f0c124ac6184b144cf0a4e338fd2894f7a7342d4ba9b568f4fd261f12571966270a8bfd47d8511bae85f02b47b7fc34bac5d5c5dc88a0c90ab6c8d9bedce3ef4d1ad691a6dae976a96d616d15b409f9638d70054a1dbc68ea51d4329f4619a8022b78e04548515117b05000a035c5c4702a995c26e3819f534047bcb68a458cce866719540724d02e41c0f7a012a40f6141cbc8e7bd01719e38e6838af1c0a04ca8206d3cd037bdb082fad9e0bd8a39e0718649141047d0d5d18f759fc0cd3af164b8e9999acae4e4f81236e898f7c0f55fed574615aee83a96817ef67abda3db4ebdb7f66f983d88a061bb8db9e3d45165076db83c1f950a53780d8247c80a2398f182724f1c7ad080c608cfa7a51a0062adc7afbd0130173bb9c5070f071cb37e82826106e8f615e01c9e680d6b35bc534be3c1e3831b2aa962bb188f2b71df1de819ae4b1048c7f57bd01a58268e332642ae0704f7cf6207af6a01b99e17b7b6416e227407c494139909ed9f4c0a04a4e501e0f1eb40d263e53dce7fa682c9d0bd13abf58dd6db18bc2b157c4975270ab8ef8f563f21447a73a03a1f4de8eb031582b497328066b97fcd21ff038edfde88b7e32703bd64188e7e6283864b73400cd804b67ca3268317eacea6d56ff005233592f8b6303f953fa4af7c2fa93417fe98b763e0ea171297bab98558068f695ce0e08fdbd281e5c6a57ba5e9d14d716ef7774f2ec112601da4f27ec2827ada74bab559a20e148fcae36b0f91140283729c77a0e0a7777a01dac68395719e39a029607cb901b19c501480ab9279f4a086ea8d0b48d76c0586b7143224a76c61ce1831fe93e86b43cd1f12fe19ea7d2533dcdbeebcd20b612651e68f9ece3fcf6fa5067cbcf20ff009a051724905411e94032799060723da8406d6c67e7ea68d0e1770fe5cfb5026c37039ef9a02eca098c91e6e01e71c500b1d8a49c12786cf6a06a4e256008e3d050119958007920e2801154e32fb4120927b014017eb1c523ac5209a356215c291b87be28957ef853f0d66eaa99352d515e1d190f947669ce7b0ffa7e74a8f4be996569a5d9c56b6704705b46bb5238d42851f2ac875712bc70b3c30f892019540704d01ad2669a0491936330c95ce7140b2e4939a03638c7e8680ae485e33bbe540d60d3ada162c90a02c7270a39340a4f28b68da4645007a8f6a069a746f73235ddcefc391e12b2e1916824948742c99382473c73404791c617695279dc0640f9502c578c9efeb4095cb4cb0830ba21cf999c6401f4f5a05061d430c8079a02e03b3004311c7d281b5e3cd676c65489ee594e4aafe6c7ae07a9a0a075bbea3a8ea96f047d3935ebc404f04ad29411e08e011d98fed416fd212ee5b05b4d5ad6300c615807f1171eaa49eff5ad418c7c55f8466dd66d57a521f20cbcd66a7247a9283dbe5418a63862479877cf1f6c5008e400bdf1ce684016fe53dfbd1a73794600e08ce3d6800377c8c7d6800a9cf75fd4503d91492460f7ee3d28247a7b459f5fd592d22711c206f9e563858a31f99cfd050583518ba75247b1d134f9aed21396d4669769931dc01c003f7a329c4d17458ac5b55d36c12e040a3f1da75c1cb04ede2447f7f6a94567ad7a66db4fbbb29ba7d65b8b4bd8ccd09c8231eaa07b8ab04a7c2cf87b3f53ea8d77abc72c1a5dabe2452bb5a561fc83e5ee7e541e988218ed2dd22b7855228d76a46a00000ec00a510bd4dd511f4fe84da95cc31f880022da4902b1e7d3e99ac86fd03d631f565b4ee6d4dbbc649009cab2e48c83f514165b8b94b6895c44f279c280839e78ce28178ae6de46748a789e453865570483ec6812d42e85a421fc37918b00a883924d024c6e99b7a2a966c0009e17dc9f9fed40f81c77e28139218e4ff9815b9cf23340a01c907b9140201038ed402fcafd28386464e4fd33c50272bc60032609cf00fbd024f722dc66f24822ddf972f8feff00e280f69b24844919cac9ce7de83a447f30ded823007b50459d6ecacb528349b979127651b1dc795f1f3f7a0990148054823dc5015d491c0a0c3be337c2ff00c489b5ee9c87172016b9b541c49ff5a8f7f71eb560c1fc43e0a47e1aa94277310431f91fa551c1727f29ed409b641c86e31839a3454805739c1f6a026f1fd740f64665fc8c31cfde82db79bb40e9e8f49b62eb7d7e8b717ec832c91ff247fa1dc7df2281bcc9369d671493c422b7911654c1215f92bb8827bf068624ba635392df5eb4b9924558ee5bc19b71cee43c6dc7cf34c657be8db0b0b9d0f51d2afe668934dbf9628ddb8c2b8c0073f3a80da37546a7d25174fd95dc125c69f7313ee5655dfc313bd483cf07b1f6a68d5b48d5ec758b612e9d7293211c8fe653f35ee2a084eb9e8bb1eafb3582fe496278f3e1c919fcb9f97ad03ee8dd017a6741b6d3229dae161057c5750a48249ec3eb4139238568f6a9e7b103b5037934cb3793c610a2cd9277a8da73f5140ee38f6280c4b11c65b934023006d50050030e4647de80c846de3b500fcf9fbd0197273ed4007b91400e580c8e45074a82400e72682b36fd2162b7f25ddc09af2766ceeb872db79cf00f6a0b3229550140e07007a50092db860673de818df473c862686dad6470d9cce3b7b63e740fa1de6252ebb5bd81cd00bee2d800d003a6464004763ce683ce9f1cbe1f1d3a67ea1d1a30b68edffba814708c7f9c63d0fafceaca31e6dc71e1f07daa82608c83819f7a1a11ce149238fd68d0a579ec682cfd27a7c3a86bd10bc38b3b756b8b93c1fe1a8c91f7381f7a034f752ea5aa5c5eb292f732128037619c018f6ec282e5a2cb047abda74d5ce9b6da80f136de4a496219b3e48c92000323ea73467519d3da5bb757dbda410ac90c77c23058f99007ee7ec31416882ee47d23acb5185caf8bab4691b1efe57fff0038a9457ee75a82f6e7429350466b482f2742c0f74241c80c38c64541a9cfa1e89ac0177d33ab3d8de28f2b5bca429f91140e2c7a9b5ae9fb85b6ea9b46b9b3c796fe040768f76ec0fafb1f9505df4ebdb3d4edd6e74db98ee216fe68ce47d280648f75e2485a44da385ddc13f4a025ddbdbea16a633286566ce55f9c8f6c502ad750db2c514f30dec428247e6340bbf04100b73402afb943ed2b9e30683836defe9403bc1e06734020e06280cafe8683a375941d841c77c1a0151b467b50159f00e4127e5402872371040c5046eb5aadbe9b1c02e2f6dad25b89047099c677b7b0140fe3f1010afc803f3018e68160c3041ee2823f5dba92d34db89a1d9e2843b03b6d05bd013560c1748d57aa2797c6b35bab78e6959dc47231580ff336dcfb03c1a58364b5bbb7d7fa7b7427f1f673830c8664285bd1815238fad20f2c7c41e979ba43aa2e2c1cb1b663bede438f3a13c7dc76fb5515e9065b851f7a02950002a09c51a1b83cf14176e90d3645e9ad7752752aac23b3439c066665c827e944d29a6410aea725c4567135bd840d3c88a723728c29c9efe6c50d3ee9545b0bf8ef2e6e3c2fc2c6f72f2920e5f19039ee4938a9a875d03278377acf52ddf867f036ef71923932bfe51fbd3475cdc369df0db4fb389d4ea37970fa9cc0b00511795ce7d4f181eb4cd2451755fc45ac16d637381b14ca36b641dfce723e4053170d6cb52bbb362f6d3cb19241f2b9029862f09f143549ba7e7d2eef6caf2797c66ee17fdfd69862d1a069da7dfdac579d17adcda5ea9e1a992376c4723e39e3b024fd7e94c458ac3e25dee8d31d3bae74e7b79002bf8b8549471db38f5f4ed4c165e943a06a328d4ba605b4b22a1523c420c64fbaf38a82d36f0ce7cf7463790729b53017e940e0b0ceceed8ce0500e1b70daa08f5c9ed41d271cd0132476e7d7ff00aa069797d2411168ed9a41fcc858211f73c5075acb25ca6fb82aa31e58a36c81f561dcd033d42169e158ac64b98151b3981c2966cf639f4a064c7a8ac55e4865b7d493701e1c8e52403ea3cbfda827e390ca3f2c914aa81991bd281cdacc2747215c60e0ee5c67e940cb51b0b2bcbd824bfb08ee1a252d1caea1821cfa67b1fa504982b2283ce08f518a08abb82f6dd0369a5662081e14ce40c7ae1b04fda82275cb0bfd4f4536f7114589a5412461f3e4ce4e0e060f63f6ab2893d3b4b5b5b78e22ed22aae3cc3cc7e64fad3449a22a461500007602a0cd7e3b74c26b5d2ad79147baf34eccca40e4a7f30ff3f6aba3cd0543267eb5427b86f1f4c76ef45d0eca1ad5ef224d13e1cf4fd9b22192fa67bc955f8c8c617fba9fb510d7a6ed3fd43a735e5b54964be658c048fb6cdd9e7eb8a186bac97d174e6d22e23437b7ac26b95e77c68bf950fa7279e2b22dba45b59e97a669fa4ea36aeff89cea9a90451fc355ff0096ad9f4ce3f41570675d4fa8c77da8de5cde5be26bc653171ca47dc1f6c9fed5562b97f70276808da7c24f0c1c63804e33fa8a2928c0e0383c8f7ed41d92a41393f4a2548595c2c37493db4cd04e8a08f139566edfef3445b6e7aeaf65d2df48ea2b11776ae02a93e564c772adef409f4ee8ba9a21d73a36fa579ad9f325afe599171ed9c30a960d5ba0fe2843abb47a6f510fc26a4c36890f9558fcc6783506a1147b510024e30339ce680d2c6ae9861eb9a009178a0205443b989e39cd01d8075e3047ce80563057ca381ed4011c4531e503d85013c91b804a21279c903341131cda8c3abdc8650f6d20c4321232adec3dc504bab2c113c9293bb1963df3408dd4b75e1efb2856463dbc43b4631fad047e9177ad4fe32ea16b1db4b8fe1aa92571f5f5a0916bc8e0895af5c46c17cd8c9ff7da80f6d736f7f6915c59cab35bc837238ed8a072a31c1ef4062870718a06f7702dc5b3c522ee4752ae0fa8230683c75d6ba3b74ef535fe984929149e4278ca9e47edfdab42058003763ed409f88ffd6dfad06b1f12ae612fa0c76e0b471e9916d23f973eb4158d3efeff004a984da5debc1295d8e4018dbf3145d583a2ad96f356bbd7f5d90dc59587f1e79a6392f28fcaa3ee47159444ea3aa5ddfc7acf50dcdc344d7a4dbc317f52641200f6000fdeb41b5ef51d8eab672ffa9e971c97c11638268e431a46000012a3b9a351567db823b11f3ef40948e428048207a8340ab48ae83cb83ee0f3428a982719edf3e68c9cc97d3fe15ad8c9be138f2bf38e7b8f6ef40f7a5f55bdd3f56b46d3649127f1405f08e7249c76f5fa50689d48ba5f545cdcbdb462cba9206411b2b055bb07d4fb1c73528d4fa8f52d62cf47b6b8d2e65fc458c49f8a818795c151939f977a823ba0fe253750eb7fe937b04293f9f6c90be41dbdc7ff006283473c1efc1a06f69776d73bbf0f2aca32572bc80470450284a46dfca19f819f5a04e799614def26c0bdce09cfd85045dc75769d12dc3c3e2491db0dd3c85195235f7c91cfd066ae0cdba9be31f4ec61a386c1ef9d4ee473e45cfb1cf34c101d3ff1ac9d481d46c628ed24751881880833f988e7b0fa5328dfed2f2def2ce2b9b79925b791772ca87208f7a60182ee2b95cc0c48f53823fbd40ac658b30f4f4a086d4ee1d75bb6b78f4e965596366fc5211b23238008fde81f43692da5bc30d97831a0397dc09e3d714087506bf61a2c4cd77324726d2caaec141f9fd2ae0c435bf8c57173ad7876f7a2daca10489121244cdf319ce3dbf5a834fe81f881a6f57bcb6ba7c53c72c11873e28cee1db391dbef4199ff00ea4348116a5a66a8a8a04aad04847a90723f6ad7d18c312ddc02a3815423ba0f63fa541687bd9efe1b533b3c9e0a78473e899e318a09bd0ba6eef543e3b2bd8e9b10064bd9e4da001dc81401aeeb29a984d0ba7d5e1d06d4e6594f06523bc8e7f5c0ac8af752dfc17d7090d9218ec6d9447129ee71fcc4fb9cd6842ab10dc0014f3e5a2c1704b671dfdc734525226dc939e283a362c7f940344a380393df144733e2276e38f5efcd01b4bbbfc3dda4a9298a44395902e4a9c70682660d4265d62de40b1bdc1545054f95c8fe627df141af7c3af8808f3dd68dd5d2a45765884b8908d8c3b6c27b7a77a945d7a5fa474bd2ba8e4d5748b28624955d5d8b13b79ee9e983d8d40a753758c7a46b96f6114725dc92279a2810b3a64f94900763cfafa503fd3b59b79ed84da34713c0cd890f0a158fa1f981de826e1b548959fc4dc5cee24b6467e59ed4101ff19e9f676baa5d6a72c50adb4ad1ac790ccc076200f7ad41e7df881d79a87576a5f87b0f161d381db1c2a36e7e6d8ff3416bf87ff082c6f208ef7a82f22b9761bd6d619785f6dc477fa53705ab57f83bd297ceb1e9caf67708db9c4526723e849e3e94f212dd25d117fd29a8c09a76b534fa39cf8b6b71ced38e36fb73417f52e64548e34007e673e9f21ef590a1c918c90718dc281a69b68f67118d9da5058b798f6fa7fe280daadd1b2d36eae70710c4d263df0a4d583cc7a668fd4bf11b5837d7c93dcd9a3146959822a0e781f4cfa55161e9dd7fa67a4f55b9e9aea3e9f81fc09ca0ba118998fcdb2338c7b528d39f4cd2ba76e2d357d292df4eb391809963420ce1b1b576fa1e7359119f1eb4e17dd033ca172d6b2a4df303383fdeb5c8f2eef3bce4e0e335684cb0c9f354160d36f64b0baf16072b91b5f03391f43c51aab23a5debe91c4fad4d73689e6fc3a290573ff4f03e59f4a3280d67581ce916567f84b58ce0a1fccec3d58fa9a084de08c90464e4d1a8e419059b201f4a05630a176918efc50176293872c17bf14042aa0125b03db14046c60b60123fde6827fa0c68edd5365ff11346ba6292ee64194240c807e59a32b7fc51bfe8bd5ed5db424860beb62b89218422ce09c11c01dbbd0660ae110bf1bf2154838dbebfefeb41a8f4cdac7f117458f4d9ecd2df53b4cf81a822808c47255c0f7c8e7fb54a2ec2cfabba3b4b4b8d3af12eedad40926b0f070a13f9b633649f7a82eba6ea4357d321d4ecad512daf20df26e016507fa4fbfaf3e98f9d067dd2bd2faac9aa4d72d72d1e9510ca46a7631c7a320e18f1dfd7bd059afb7da816d23de4ba5de211346a1e4785f190548e4648c63b64e6b43ce9d5baafe3b539c5b452dbda46c638a167cb281c73ee4ff9340e3a3fa5f5aea4ba58f4bb57dbfcf2b02a8bf7f7a0de3a5fa0b50d2a2d92eb3e048c0a97c867dbedcf6a944e5cf4f6b76d1b3d8ea42795066266c87c81c65b9cfaf15048e83af3cd64abac08edaf01546c38dae4e0657ee6826e5b892de3702292e2545ddb55700fd0fbfca81c4b3bc718716eef9eeaa402280d14ab3c0b2c65c06fe571823ed40df56b217fa6dd5ab9216689a33f2c8c558307e83b8d77a37aaa7d22f2512c28768800c9954671b3d33ebef568d0ef7a7749eb0b5bbbb162d657b32b46d2e1564c8ed9c5644d1b0b9bbd261d2a440af6cb0e2e5b1e7dbc1238e0f7a0375b696daa7496a3a4dac8a92cf078685b271db04d391e40d5ec4586a1716de2a49e0c8c85d3b120f715ba1899173ff305413070abd89cfe9f5a2d3ee9c8639fa874eb6b804c52dc46b20c9f302c3bd11e84d47e1af4d5dc6521d3e3b662c19a58721ff5a9a321f89bd27a374b456d158dccd34d333332c9b4b2afbe47a7cb1f7aa33d2bc0d8c0f1c8f6a2c14b6d501b39cf63450897380c319e3de8065031c038f7ed40d8faf1ce41e4d004876a8dc3cc7e743025c956c818028c904579e7f0e15695c9c0541924f6c00283d0bf07f42d6b48820b8d62d20b2b58d656404959e52f83c8ff00fcfafbd4a35bb06f12391a48dd55cee2b2f3818ed8f6a8158a159890f02242079147623e631c502b0db436d1ecb7458d4738038fb0a087d6eeb508f48bb7d32d95750752b6c26c905b3ddb6f61eb574794f5cb6b9d0fa9678b512b25d24bbe52b8c1638278fbd582c57ff12afaed45b5bc0d0d8a8c08a2731ee3eec5793f40450466a1d59af446293c186cd53ca0c36eab93dc649e49fbd048e89f1675ed35e301e293919dcbf9867b37cbe94a35fe94ea4d33aba6824306dc48015750d86c6e247b0cf63591a40b8dc23fc30f14138dcac3000f9d03687547f12e8dd5af816b13148dddbcd29039c0f6f6f7a0eb5d62caf5636825db70c9bc4328f0dc0271c8a090627d3073ce681acf6505ccf14d35bc2f2c2731bb28254fb8a075144a83ca806792400334049ee6281e2496408656d880ff0031f61fa50446bd76058ea1b9e21025a3bb48afe71df9c7b71de9c8f196a0de23ca7b827d4f7add117e0cbfd4b5059392369663ff004e71c51aa97e8f555eadd258f2bf8a889cff00dc28cbd0bf123a926e96d163bdb74490bca2321c678209ff001591e71eafd7a7d7ef45cde2c20aae144638033fb9ad2e1b5e69d058da431ccf21d4a5c3b4631b62523807feaf5c7a50222f2d648c25f5aeec8c2cd19dae3d3e87e944d3eb7e90d425b49ef2292de38224f1505c3f8724a9eeaa7bd0d57a60406059436306868a7803839c7ad1a158039c13f4a33a716767f8cb9b6b55e1ae2458813e9938cd07a9f42d0b4de99b4b7d1f41b58ff19b03c93ba06607fa8b1f5f619a5b8266d74a65d42da6ba90cce996dcdc8c9fff006a5a2c2635083b05ef83eb5028076341db4b1ed9f7a04651fc41db18ed419d75b744dbea335fcb0db0335f2057901c05da73c8f9d5d18a75174a3f4c47335e35da4ce418a489374254f707d463d33565d1529b569a489a17944b06ec8057d71dcd037b4b6b8bfba31584124b27e62a8a4f1ea68357f83da7ea5a76bfe0912453ccabb49194653cb60f6ce3dfda983d196cd108c2401711f9768e306b2297d73fc6d02773a8b591922693c5004bb9d72542fa2f6efde8314ff867aeeec27500b77bb5670e36ca19b1dff2e7f2fd2837ce8bd5dd348b78b552219022870d9c46e792a4f6c608a0b846c8e03232b29ec41cd0199f1410fd4b24b1e8f712c0a5e4452d851e6c639dbf3238a0afa42ba77475e4ba8470896681da45180b18da76af3c9029c8f26dc1df2b9c606e273e86b743331924f27f4a82c12280e59b008e79f6a2d4d74188ff00e30d203a82ad7519c1ff00b860d11ba7c5e86c9fa3afae6f4091e043e021270b21e01c7dcd6479ab4dd3aeb56be4b7b184cf2b301b57d07bfd2b4bad0fe25e9f6960ba7c7a55ac50cd750335ccaade7723b83b8f6e38a2207a5ba4e7ea3d93780cb616ca53781f99fbff009a0b675a5be9765d43a75a6ad3b25adb4185429b831c70303dfdfd2831eb8954ca48f3827819c71ed406b2b1b9bf9a5fc1c4ce2253238047957dc9345d122b792eee522811a495ce1157b93ed444ff0049f476b1aaf51c761345269d25be269259570c833c6077249e062a68f53e8ef0da69509d4ae225b92a04af232ab16f98cf1f4a5a266d4dbca8af13a329ecca723f51502d14f0cb9f05d1c8ee01c91f6a0393b4edfe63c8a031608859b38f97340d84d04e5846eae50f9829ce3eb400fb24466041f5e3d2823f56d22db57b192d6e61468a41c823ff0035651916bbf04ada7badda5cad6d1b72c09dc33f2a6875d25f0865d06fe2bc6d4c4d3282026cca8cfafcfd29a34cd234a10c768f711a78f1bb392a3001208e3ec69a26a58d640c832091c90706a084ea1d3eeafdadf4f86da3166c0b4b397c18f046140f5ce4d04f4702436e91c28a9122e028ed8a0a9f5a5b6a09a1bc5a135bc72cce048b3c5bc15c638f9d59043fc2db997481aa69dae49e1cb6bb643239211939e467818f97bd305965ebce9a10bc8da9dbaa2679dd9ce3d8530572cfac87566ab05ae9f1490692b9696e1f833738555f96793504df5f25945d2576b7ec16dc46792381c7b7ad5e60f234980e42f6c9c56a82ec3eff00bd4124e49700f1c646e3cd169ce9575f83d52cee324347323f6e3861ff008a23d47d4ba6a75074fdcd8ef317e2e2ff0098bdd4706a60c3f4ae8cd5f44eb8fc3e97248a638cbc73bf90483d463b373e9574685abf42a6b5649fea72bbdeac4a8d3b018cfae31f7a6895b6b29b41d30d8e9f6bbed9213e1b7a994e724fcbb5064bd7835a9752d3af75d8116354778f660788cbd9483dbb0a0cd20b2b8d43528ad2088bdcccf854039cff00e2827a0d34e9da1de896f2182492efc0976f998aa827d3d334113a74aa9a9298628e74570478bc0c7cf1da83724bb8246d3e6416b0384da61b5501c9f5c3704f152c037561a95f5fce61d3ad6db4ab950f34b331dd9f4191db8fdcd406d67a675ab4b6d325d1af248272a43430315ddec7038f6ad4b3f448bf47eb71cb69abddebf21d5e26896203846c30c8603b9c6452d9835901405660376319ac84bf13180779d8bb82827d4fb0a06f777367a75acd7170f1430a9f331200cfceae061a0cf6dac692d7365266191db0578f5edf3a6075a6c9278b3433188a467860d96fbd40fe540471409aa0c1140750001ed8ed4058e15133c983960077edf6a06faade5c5b7822d2d926766cb967da2341dd8f0727d85033d27597d62e2ee3163756915bbf8799d71e2f19dcbf2a092b88dd9a311950a0e5b70ce47fe6ac18af53f5b69da9752dd69da9ca906876e24465d9e69881c6ff005c679c0aa2bfd267a347512c93dbb5d42d90d3c800b68c9ce0ec3cfa528db74ad034db5905ee8be1ac728dc153984f3f980f4fb56453be2de8f647a6aff53796596f0aed46798ec033ce149c0fb0ad71479c9bb9dc3bf3c55a0b95f65a825150b481a407b93c0fda8a29c06671dc93803bd131eafd0af6dffe18d2ee25982a4b04603b7a9c631fad03bbe586381bc5945b96385718c827db3eb5288eb8ba934eb15fc3c535f05427796dcccdec7150637d5bd55d5362b7975aa4d0d919018adec8637807bb60723000e4f7cd58203538aefa8aeb478a7b9beba924547b8774cf8608036a80704639cf1f9855d1a7f4c68b67a03de5e5d59dad8d988c62e1c0f107a1e7fdf7a082ea6d07a6e3e99375a7cb6b3db093c727701e2360f7f53dfb50653d4130d42ee18f48b3f0232a15218936963ebf5fbd06dbf0cfa74855b9d46e04b730c6144691e12307d33ea7de8348ba6b5478a279a004f98c479247b81f5a9438805ac0be2e02e73c9ef8fbd40c2346d43578eefc40da7da1dc8b8eefea4fcb9fef419beabf12a4bcebcb2d2fa7ee0dc58492084b30236bb6467dce383f6a0b87556a67a7f4d95a0bbb5468816f0a69c78b2e072572719ce78357079dfab3af2e7a92c963b88d94abbbf91cedc93edf418aa2c5f0dbe2a6a9a0c90d8de34773a6a8da1186d6403fa48fec682d9adeb7a9b4c9d572dacc9a6c9700456e5ca910e000ecbd8e580352fb1ae7476bd6dd49a325e5a9f3025245fe961dea097523cc0919a032af039a006936c81423104649c703ef40dcce64bc3035a87b6f0c378f9fe7cf2b8fdf340a4b6e25962915d94a67807839f7a043586922b5636ec44c061063f31f6ab079d7fe19b7eb2d4efeef55d5d74f992e9a0fc3a441dcb13927b838c9aa2d4bf042c618e178efee6e18104870172318edf5c1e6945bbe1a748ea7d2315edbea3a99bcb190030c401010e4e783ee0fa56455be3d6b90c1a6268d69e17f1486900ee98ec29ccc183119419e7e55ba11f089f523ef5058363a8059fb8e31e9421b491056c01819e28d3d0ff07eea3d53a1e3b6b8db235aca63c139c0eea68ca47a9fa6ef757b83ff00bf68ad428c2f248c7a8f9fcea518df516adac74e7544f63a2ea172f1800291e6cee19ec78cd5826344e85b6bad25ba8fade5b99dae0ee11efc71e858f7e7d054a2d7d39a75ae8f7b6b00b8917f1516624b78429da327cec493db1db1d8540cf4aea28f58d6aeae2f6dd64b498082d880488d149fcea7d4939ab04175e6850a8d32de3b78e380c8de32c4db4e18e430fef543cf86fd0d691b4fabdf6648b3b2db69ce7dd87be68342d2f4fb9b5b891af1a28a2dc05bc5036d001e0eef7352884b961a2ea9aa7555c885e08d45b5bc52b61b686c120fb939fb541276bd4b61d53624d942e2f6200bc32290633e99f4233416dd3ad3f0d611c0c77b632e71dc9ef41156dd27a45addcb3dbd9c513b1dd941821bdc7b558333b9f873757fd69a85e3f813e9c7723b5d93265d872473c11544a68ff08fa75e290b42ec4e4124e70738fa5048e89f0f745d2aeadd2decedda6525c975121183c77f7a945c754d0e0d563682ed43425369403bff00bcd58308ba7d5fe13f5a05889974a9d8b46aede4914f707d88ff001528ddf4fd7edb54d1a1d56c312dab2e64dbc9418e78f5c541296d70b716d1cd6f8789977230ecc280cb7519b816f212b205de4e0843ce300f6cfcb39a0545c42cee88e0b458ddec33ee680eac92266360debc7b5056fad2d354b9b189745744be121daf27e550548ce3d4d58324d07a725e98ea2b7ff5381f5169a7579d021fe13904ee43ddfbe49038ab46e76cf05cc714f6d309232a4a98ce54fd6b2196bb7f2e9b631b2c427b891b6851db3eff002007341e5bf887aa2ea3d4f77378be381e42fdb711ed5a1554395caf1cd07617dcd04fc85402101da791421b49920331381c60d1a69bf02f56f03a925b12c162b98c955f775e47df19a32d99b518268e4491668704a79d4aeec7b7bd4a30feb7e9144d76e265697c3e2693631674273803e556087d76f35fd49859e9925ccf611141106f2e182e3241f727f5a94681a268f79ad1b1b8b9dd66b1c2b1ce9bb06361c1e7bf3fe6a096b0d3ba57488e485b52b40909c386901607d47bf7a0ae758eb69ac4d15be81a748f0a9c35cc90b2eff4c03c1c638a0b77405c5d5d45f87be5fe359a88b81b401dc1c7d38fb50586fed18ea3015790091591e447c1518c8c7a0a0a5754d8c9d49a8d9f4ee9dba0b3b5224b9692327728f627e7c6682f9a7e996b6b3a8b6b748a348820c7720761412c064e3041ce282b5d4bd73d3bd3f33daea97ac2e540dd0a292dc8cd043c1f15ba2a7923b65bb910371b9a12141f9d02edf13ba2ade56857551e5e77244c54fd0e280746ebfe99bbbd655d56dcdc9ce08465565f4ee3bfca82d53eb3a6dac3e25c5f5ba646402e33fa77a0aff5b74ad8757e9ca972844aa37c520fcca7d3f5ab067bd369a8f467544d626c98e9f7118f0200e4465c903049c8c9e6ad1b24334b6fa6249716cab20037c309dd83db03b5640dddac3764a4f02cb1103863919fa7a1a06d6f600c37162911b7b252b87dc773f1927393f4a079f868edae1ae6328a8b1ed38e30050226e85d5dc1f879011b3c47c2f604719f9d01eff4f4b83e3c6b18bb452b1cac9b8a83de80b16e8208a3b7b58e1407cc061427cc0ff1560ce7a8f592d69a97504cad2dac01a2b53900c3e9e51ea58f727d0551e73bfb86b99a49a46dcf21c96340dc13804f20f6f9501c0e3b8a0963316fcc4607007f57bd084d64dec01200ce483468ff0040d525d1755b4d4206ff0095207c11dc67ff0019a18f56584f6daad9dade4211e39104a8ded9152b235cd8c530613229c8c1c8ef50472e81690ee00322b0c100f0debdbb7ca8111ace856371358cba85aa5cc407891ccf83f2ef4048b4ad2e59bf116769672c72f99dd1437239078e2824a4d3e1b94559234110e781839fa0a0561b38ad532a12319c86c6307e740a9732a3a00cac870cd8e0faf0681be8b6db965bb909df3c85806eeabced5a09523647e6e0fef419a6adf116daf7ac34be9dd1da686e7f1ca2e243b76320ce57df9ff1560cc3e3f470ff00c78255b842b35bc6c4af9b6e323d3e95467b6365f8dbcf062beb68c119595d8aaff6e282422e9899b4f6bb5d46cda2562a76316c1078f4a0859e1b9b762c0bf94f0e84feb4125a57505c58ea70dd5d0174a986d92b1c13f6f5a0de7a5be366877260b5d42dee2d2423124a487507ebdf15289dd3fac7a7bab6feded74d61733473acdb5a162142ff00313d81ed505fa58fc6d809380c1b9f5c502e0e05040ea367a85dea454de2ff00a610375b04c16c7a16ef8340b5f6930dce9375636acf6a278f04c5dd4f1dbf4a084e91d06f3a52dee62bbd4a2b882494ced3c8a448063b63b638fde803ab7ae749b2b3096d792c93c8c109b55dcd18ce3710473ffdd043dc758dc5869044565aa5dda4c3c2b7bc78c1f14e3963db03e7c0ab066bf1327d41ba76ca6bc48ecad24c456f6b0c87cf8e4bbfa138c0fa9aa3297c83dd4e28395811cf2680a5b93c7ed413cd1ff0f3c797b8031406645236b0508406f30e68ba49c051b97d0e0e7d28ad57e19f575c5be8f269515dac772877c11bc464dea7ba8c739ce78f9d3193bb8ebfea2bcbd6b5b6b8b58bb7f13c2f0ce31cf0deb4c0f2dbad6d743d2ee99efae752d6c02a86e0054524f6383c7ff94c0b6af274c75149a46a5a82c46f1e1479fc3190bd8156fbe7f4a960bf74e9d253f1167a3ac09e0856610e3041ec7f6c540f67b892cee7f8d18368232ef2af2508c7047cf340ead5bf130accc9b1186541e723d09ffc5033bbb1b82d74d6b37f1244daa1b38073df3f4a08eeb1d3b50d4fa6a5b4d32f12cef1902ee73e523d476fde8306eb0d3fabfa4ba92c278af67bb7281606472f90bdd58558253a6afb40ea1d62283a8b461a66a6f931cf6a7c2466f7cfb939e7b5515fbed3747b5eb8f06eb78d35080a2ec9719c76f98049a0b4ebdd37d1bad869acbf0b03c5c16b29444adf50ded41995f68564a263a66b31cd02be152505493f51c1a088bab69ad1bc179e320f07c37c8a0692b46c4995f0381db39a0b2fc34e971d57d4705bc8db6c50ef9dd97b81fcbf7381528f5ae97a1d8e996d1db69b0c7648855b10a81b80f43c739c54134147b9a036063279fb5046e957726a0f2cfe04915b06db1788305ffeac7a0a00d72f8d9c491c06337533050ac7185cf2df6a06da2da4293488f34973328c34aea428c9ec3eded40ee7d2ad249448f6b133820ee2833df3fde819ea96897461b05b87815f2ee919e5d47704fa039ab079b3e326b70eafd4ef6d6650d8e9ebf868b69c8247723efebf2aa280eb9193ebedc5002a124e015340018fb8fde82cf32b1603d0678cd02406dce3008e47ce81b499c331383c9c9f5a2e9c69377369f7d6f796a4acf148acb83fb511e91b3b3d0bab745b7d45acedd8e3732b71b1fd73f7a5a19eafd09a56a0a96b1c705b49c48510761ce4fcfbd4d0d752826b2b583476fc3daacb295b79d768de8a32b1e71f989e49f6a7d14dd1af5ba275a45b8b093c054492ea769092373765c1da4679fbd306e36ba9595fe9f0dcdbcc92c33e1579cf27d0d409ea178f68521b6b76926ee8a7853f7ff140bc768d78f6f73748d1cd103b543f0091cf6efc502f7319dac194371d8b6326829f0c501d7ae6fa568d5d4942c806d4db81839f53c8cd59456fae6e628749b5bab8b1865b08e4726588ec11e7f2e49071c93da9a31dd4341d675e9a5bad374f9858162d0b4ac70e18f0573df35a0c759f87bd53a404f174f965dfff00f479b1ef570576e34bd4b4cc0bdb3b9b7258a00e846e3f2a94376475cee4914af7ca9150685f09ba61efb52fc7dd69bf8eb7c158d1d0b47bb38f37efde968d6eeb4eb5e91d6ad25b660aee59974db6881690918e31ce39279e062a5a34bb57b88adedd1e379679065d80036679e6a07e8391bce7e940c659ef5afe1286de3b16f2b8903094b7b2fa7ce81eb380c4260ed193f2a0cd6fa5d4a4ea0fc7bdadcce923158a3039db83c038e3ef41a0e96b2ad8a35e009291b8a939d9f227e43bd590436bbd6fa269202c974b7123602c76e779624e00e29833bf897d493e896525dbcb2a6b5a9c3e1456b91b6d60cf989c7f31f7a60c02490961ebcf3eb541308e39e067b507007b96007a67fb50178f97eb4165ce18165c2927b773fad023202d9c8dbb7818ff003408300b87f2f1c107d0d0c15a4f2e339c90467f6a18bdfc2cea8ff4bd561b4b9ba686d6e64552c4f954e7d7e46a60f4688d240af1b2bc6cbf5047ca960617ba658de1b792f2d94a5ab33461b18524633fa1a81b5c8b5168967369d23c0e0a24622dc981d81c76aba29df0bb48d660d52fceb88d069f04aeb69130037127f37b9c0ed9a8350781240bbc06da72323b1f7a0eb8816e633192ebc8c9472a78fa50349b4c83c068e24f0ddbcc1c13b837be4d055b57e98b996d4db5b4a893dc1e6620b6ccf2c467efc504ce97a38d3f4d874bf09af6d46e2f25cb82724e791db15650a43f878b51fc34f3da8f132b6d6a98c80a39ff007e99aba249631b58b9047239ec3e55368aeeb7d2da6f52c0eb7f16e87f2c6e836ba90724ab7a67b55d115ac7c3e8aed2182def4c56a14096368959a423d77e3229a27b41e9d8343b01069c8a8dc9660aa3713df3c64d4a1c695d3d6b67a8cba94b9b8d4e61869e4e4a8c636a7f4afcaa09a485519caae19b966f7a0435196582c656b74df3e308beec7b50629375775b691ac5bdb6b16d6378779f019b00a31cf391c9c2f1daae0b35ef52f5374de88d77aa45a6cd25ddc0108694ee2188c28007603d6a0d16c92430a4b2ed3230dc401855cfa0a0a07c45d7b5db9d462e9ee960b14b2ee134ef8c850012147ec78ab0670b643a2efae753d72686e6e2da211db42176079c8e768f65e39f7aa332d6f58bbd635096f6fe6692695b24f603d801e82823cb900ee00e68006460051dfd680ed9f0c905b713d8d006d5f5419fa505a18f94e40501b1b81a04186d62402c87be3d6810b81290aea8467201231cd1749dbc437f9f1e201db3de8ba07dc0175c027f28a335b17c26f888d6b6d0e8fabf892a29c453b1e547f49f7a946d6424f08236491c833ee0835073294888894120700f0280813c40a6711bc8843e00fca7d3ef40e41dc081f9a811681c6f7565329185623b7e9de812b3bcf11ff0b74563bd50494cf120071b97e5fda80d7577046c9019d5669dbc340324eec67fb734103d5da96bf67a7cf0e916f6e2765f25ddc4c11107ab1c8c647cce2816d3ec7f0f6564cae6e67da375e6d52cc4af2e4fb13ed4145f899d47b3499f4bb6d46cda49b69b92921565c3648e3dd40c81cd5c0ae89f13ec246d3e379ed2d6da180b5d34849da1780b128e49271c9f4a60ba685d5fa36bc42d95c324ec7090cc9b1d87b81ed50588958977cacaaa3b9341c655f12348d1dcb8dc1946540f99a019e2134454eeda7bed3839cd052fe2136b536b5d3563a1ca53c49da4b9507198940ce7e5c9fbe281c6b7a974cf4ee4ea7242d76dc784a3c595b3e9b464e3f6ad0ac745ccbd4fadcbabea42da56959a382ce7460d6b1a93c01f97272093ebf6a82f1ad6af0e9da5cb3cecf6902216919f82aa3818c7a9f4c530649a9f5269ba7429d472239bc991a1b0d3c3152880f0f23039e7bf3de90635ab6a377aa5ebdcdecef2c9239e59f3827e5ed54302195fcc38cd01245395c1f5f4a05b606538e483c501b6939e3b5077860f3914165754c33e549000dbe87de813b820c27fa7baafb8a04a69c98e281e42618c795338033df1f3a06c03e4e029247007ad010093c35674da71f977640340081a190658e41c820f141b0fc33f8926c218b4ed609366a02249bb2d19ce3ea4528dbece68eead926b7916689c643a9e0d643387521fea2f693c2d6efc786ee46d9bfed3eff2a04669edf5295ff057a60bd865309246d3bbbedc1efef41d63a8dec9ab4fa7dd4510fc3c69234ca186e2d9c003b7a67bd034bad0a5bb96e25d575267889cc1b54446d9bd0a37bfbfbd02925945a72cba8dddc48b3f87b1e58f23c623f292bdb7fa7cf38a0a5750f54ebba56a9a67fc516b6d6fd3970ea9234677c8dc7f38f6e4640ce282d1ac4b16bfa72c1d2bad430cd1ba822061865f5007d3daac19cf547c189357d561bbd3eee683c62cd786e9b73337b8c7bd512bd39f06adedec2de0d5ae639da372e6485363107f97767b505cee755d03a5e58ac228659af123184b7b733322e38c91dbf5a943ab3d52e64b49ee755d2e64950e238e35f10c884e17cbe87dc540e6d7509a4f110e9f7566a471712850abf6ce463e6280bacea36fd33a4497f773cf32c698dcc4beee33938edc7ad05534aea683ae61d64c4d2a69b6b88d16d5ca5c303f3e386cf61db140e27b5e99e96b64bdd562b6b30aa36c6c37cac7dc9eec6b42c1a66a962fa70beb6b516d0cbe76322f86c78f6c66831bf8b5d5d2dfa35a5dce60b1933b6ce3c788769f2b331ec1b8fd2831b79649984b239773c1dc68129725c1c640e73400ec781d8fb1a03c4a85d0c8582640257bd01e51fc42236263c9c67be280429c6037eb405dbf5fd682c2a0bb976cf07d3fc5009279ef8ec4e68193a9902b28e7dc71fb501d95b098e0f6dd9e0d0049131019b047b8390281bb292484e47c8500c4f242c3076bf704704739a0be7c3febfbae9a5daf23cd017c7e19fb107bb67d0f6fd6837cd2757d1fab34f4f05e37dde630b1c3a91edf4f7159103d6eb7da65fdbdf59dadb5e2460ac876ed9e1c8c060f9efe9c8a0a75cfc42d5742d2ee5a7e9dbb494b6d6b9bc930cce4f940e3cd81ed4160e98f88315e689fff0022b57664199cc5196f0c7a164ef8f98cd0589baffa68590985eb15c0db1985839f6c2919340b69d03f5285bdd6f4bf021424db4329cb153fccc3d09c76a090d3340d2f479a7bab3b38e2924e5e451cfd280d7dafe936f6c5e4bd89813b02a36589ce318a0358dc35cc4e17f9bf234cdbb78fa0c607a7340e6cec20b1596610c6934b8323226379edda81da8dcb9ec40a042f50b5bb21645473b58b11dbd7bfca8304f8add5d67a9ea8ba5d8ea72c1a4d8a952f10f2c920e368cf71e99fad5833dd0754d6ed66bdb2e9a91a5babb2a310465a57c1ddc1038e7bd5171d3748b8d46ee1ff005298dc6a764c27d4eeaee7fe1c01795881c9e7804fe940dbe287c4b6d75a1b1d1c986d62277c91bf131f4c0f6fad0663737135d3b497124924871f98e7803007d2811dc5b83903dc0a0333f03be7de8122df2c9a05a11e5f51f7a05ce7071804fca8033e5da0734020b0183bb23e5416269577ed0e5323078ceeefdff6a03dbcd62914c2f629a47c622689800879e4fbd046f9d8a2a03e31385c0e73da8b83ca590947dcaead8208e73da8849b3e19ce704f7c5015586d006431f5cf61f3a04ee586ff002481c8fe6191408f0011eb8e30682774dea9bbb5784492ca6385832e1ca95e3d2834be9df8c312e2db5eb4375080337000f1303d18763591a469baef4d755989ec6f6dae5a23e20b599406dd8e080ddbed41272f4dd8caf1c86d163910f9595882a3d718a035edd695d3b6a926b57d0ac65b10b4e06eedd863bf141077fd7af2782bd3fa26a1a8891d57c630948c0279393dcd04cf5875258f4de9f0cb7b7b6d66d2b81ba752d85f5214724fed41036bd79d2fe319d7a8f4b9c81e58de2f04827b9ce09a07a3acecf54b790685ace8697606009e52c377b7f2e682b097d7d36acf0f55df5edbdc0977412468cb6ce3be10af3c63b9c8a0b0751f505be9690dd5d752436f62a3fe4c6448f3b7b0c64e38f615734651f107e3045ac42b67a7693018633b965bc1bc838ee173807bf7cd33065baaeb1a95f2c11dfcd2bc51fe48880aa3e8a062a8b059f595df4ae9a74de9e9ec499d43c97b1427c6e47e525bb63e4282ad3ea3712893c599dbc4259c1627713c927de81043950df97db1406da8411c92063be280230839627078e79a0390a71b5bb5003a8c1232338e4507025573e9fbd02a0e41dc0e680c3691cf714053bb34160895dc16f291d98d02322aa39f3e14707ffaa06f202a5bb0c7201f4a343aca51090497efdfbfce89840c8db8e46573923ff14410b00490d9f5c1a0425dd8ce4673e873cd0265e4dbe7041ed814009b8cbb8e5863bd07163b7716e0607b6698060b96b7b9478dc8643918247ee39a60b7e97f133a8b4e0c63d4ee597380923970a3ef4c0e13e25dfcfab457ba95bdbddb212016501867b9cfbfda982f907c74b282da34874a9048aa479c83838edc62982b7ac7c42d235cd67f15ac5b40c366418a2cb0c1c81e6f5e31db14c160d035de8cd4a3f18ea96562cc37359dfe9cac887fef039fd6b39446f56ea5d13a9dca4579a922496b1975b8d22dfc3566cf9557230703be715ac1431d4d2275325d7fae6b4f6f182a93ef1e32a9f41938f6a60afeb1a95c5fea53dccf772cf2c8c489240031f627e7565c0d67bbf160487c1801073bc0c31f91f953420f2bc8c7c52cc540032738a809905c0f4fa501940208e73df34028e703938a0577ae013f4a001300db4f03b71407461ce0502dca8c9c7dcf6a003fafcbdcd0070bc1e0fd734070db467b8a04cb9c9e68274b93bcb1daa40200ed4099765249ec476cf340849b8b264823bf34689ee009cb671df1409bc8e8b8e770e3ec68984d9c953cf97be2860b248caaebc107dc67f7a184c31232db88fd451031ce50e76039f5c8045026efb8f93279e0fd680b239504f0483d88ef409ee25bb90c79c0e050151c6e21b39ce783eb40adbcc2cefa17bdb61322387781c950e3dbdf9c8a066f28790b22e013db3dbef54726081e63c6460d34191b1bb0720f634060e7600412c781502409c8e3d7b500ed71dbef8ed40243f181c0a02e5d4e0fad006f644e4819e3b501f7e3049e7b501bc43b4e391da80558003392d40a23305e320d02e64cf998e1bf5a032b0c927b8e68049c8c8e71c6280377043118f4e680bbff00de0504ddbb3128371c1c64668024e59f3cd02521254e4fad1a2107e48fe6a6809ddb9e78a029e1463d05027ffc744a6c3857c7b1a205ff00e637fbf4a02b12b1794e39f4a02024e7249ed409924720906800005173fd7404989698ee39e4f7a04cf723d07a501fff0097ed406ffe36a018ff00281e99a037f4d0731f3bfd28007e53400ff99a810248c0cf140bc60123233cff008a0557f9beb4056eff007a07109243e79a03778b27bfbd02b128c27039a054001b818a06609de793da815006070283ffd9}\par} -{\pard \ql \f0 \sa180 \li0 \fi0 Here is a movie {\pict\jpegblip ffd8ffe000104a46494600010101004800480000fffe0050546869732061727420697320696e20746865207075626c696320646f6d61696e2e204b6576696e204875676865732c206b6576696e68406569742e636f6d2c2053657074656d6265722031393935ffdb00430001010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101ffdb00430101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101010101ffc00011080016001403012200021101031101ffc4001a000100020301000000000000000000000000080905060a07ffc400231000010501000300010500000000000000060304050708020001090a11153976b7ffc400160101010100000000000000000000000000060800ffc400261101000102050109000000000000000000010200030405061121b33134365154717475b4ffda000c03010002110311003f00a90cf388f366a62aa720ed6ae07f96901f3831d973452b8cf36fe3570fc908e46d466433e5dd954f2e96992d9e498c7753faa44916e016ca91cc7d88b38fe60a5b97737defcbcc539c98d336a57f4fc2ca9a486bf07ab575ad9a3af4df221d8215e36df86c4504ff0024574551b3d687ee0575757b3ad64e311ee62bd94158d37e24198c43973099f1fc0c41614d950246513a081abf76cfe7061f6863281e6352fd1670949c148dd6dfb0d25f5b3689b1d5c965b0eacbf4e0932ad28e22ab9ae945633f4744bd3c8cee0a7fdf085b9000f449c5f7afa30b83e0b6fd7b0c8429c9467ff9715347c891e25fa24a205861aa715e6a09bd0488237dc2723414d9891381524e8ca7c0894664f835653631ab55ee7e3de433e4ff001b30949124e4c10c8b6ad0a479b3f9c937b2cf5bc0095ad600a0a41a0e9faee174a1c605e161c6c7a313539650b0113190f1a8368e60d5b24f30ff008ea7f0bf867fa6595feeb6978f1fe0f9c26177f4d63a51a9235184750e7d18811339cd000000c75f000e00380380ae390c350def826ed42ad051fa6f501c50f9b699c3b69cbeb76476d202bf3ac985b6e0e968be66572893e6a744540bd9722e5c87956848629bc2559306bd113e8653d3b6aff651dfad7a3ac8b02958cba02a93ccf525757039bae6cff090e1d90688e8aa233ee86a4c4a3e0586d6b2340522e47dcb7d0046d8a5acb05a123ee25d2b230b2ada6e2e2f9ede3c05202520ec2487b0d56562529d8b3393bca76adca4ec1bca508abb001babc007915d84fe3dd14e207e3c62f8379da2a3b861fb6629d28dba53b6ea388ebfed866bf6dfb553455e91ed547ae92e9445253a4fdf3efb4f8ebdfbe7d3c78f1ee0bb9e13e358e942a4ed49e22cff00eeb35fdd7ebfffd9} icon.\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 \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} |
