diff options
author | John MacFarlane <jgm@berkeley.edu> | 2014-07-26 18:46:51 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2014-07-26 18:46:51 -0700 |
commit | 31b8a95c1dc84b9351d81b4b9122f56b29b19c6c (patch) | |
tree | aa766a51032a10512bd0eac0310600e7e4e6bb3e | |
parent | 18f4490482aa4f21a1c4e4a9493fb3a88815dcfa (diff) | |
parent | 9e4604fa0b20b12177fe1f24650e4dfaf388e33a (diff) | |
download | pandoc-31b8a95c1dc84b9351d81b4b9122f56b29b19c6c.tar.gz |
Merge pull request #1453 from mpickering/txt2tagsfinal
Txt2Tags Reader
-rw-r--r-- | README | 3 | ||||
-rw-r--r-- | pandoc.cabal | 40 | ||||
-rw-r--r-- | pandoc.hs | 23 | ||||
-rw-r--r-- | src/Text/Pandoc.hs | 5 | ||||
-rw-r--r-- | src/Text/Pandoc/Compat/Directory.hs | 21 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Txt2Tags.hs | 547 | ||||
-rw-r--r-- | tests/Tests/Old.hs | 4 | ||||
-rw-r--r-- | tests/Tests/Readers/Txt2Tags.hs | 430 | ||||
-rw-r--r-- | tests/test-pandoc.hs | 3 | ||||
-rw-r--r-- | tests/txt2tags.native | 551 | ||||
-rw-r--r-- | tests/txt2tags.t2t | 797 |
11 files changed, 2384 insertions, 40 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], @@ -3096,3 +3096,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/pandoc.cabal b/pandoc.cabal index 08644d995..6597b27ed 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,18 @@ 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.headers.docx, - tests/docx.headers.native, tests/docx.image.docx, - tests/docx.image_no_embed.native, 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.notes.docx, - tests/docx.notes.native, tests/docx.tables.docx, - tests/docx.tables.native, 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 @@ -261,7 +235,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, @@ -328,7 +303,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 +320,7 @@ Library Text.Pandoc.Compat.Monoid, Text.Pandoc.Compat.Except, Text.Pandoc.Compat.TagSoupEntity, + Text.Pandoc.Compat.Directory Paths_pandoc Buildable: True @@ -420,6 +397,7 @@ 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 @@ -65,6 +65,9 @@ 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.List (intersperse) copyrightMessage :: String copyrightMessage = "\nCopyright (C) 2006-2014 John MacFarlane\n" ++ @@ -180,7 +183,7 @@ data Opt = Opt , optTeXLigatures :: Bool -- ^ Use TeX ligatures for quotes/dashes , optDefaultImageExtension :: String -- ^ Default image extension , 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. @@ -876,6 +879,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 @@ -1054,9 +1058,14 @@ main = do else e Right w -> return w - reader <- case getReader readerName' of - Right r -> return r - Left e -> err 7 e + let concatInput = concat (intersperse ", " sources) + reader <- if "t2t" == readerName' + then (mkStringReader . + readTxt2Tags) <$> + (getT2TMeta concatInput outputFile) + else case getReader readerName' of + Right r -> return r + Left e -> err 7 e let standalone' = standalone || not (isTextFormat writerName') || pdfOutput @@ -1181,18 +1190,18 @@ main = do let readFiles [] = error "Cannot read archive from stdin" readFiles (x:_) = B.readFile x - let convertTabs = tabFilter (if preserveTabs then 0 else tabStop) + let convertTabs = tabFilter (if (preserveTabs || readerName' == "t2t") then 0 else tabStop) let handleIncludes' = if readerName' == "latex" || readerName' == "latex+lhs" then handleIncludes else return doc <- case reader of - StringReader r-> + StringReader r-> readSources sources >>= handleIncludes' . convertTabs . intercalate "\n" >>= r readerOpts - ByteStringReader r -> readFiles sources >>= r readerOpts + ByteStringReader r -> readFiles sources >>= r readerOpts let doc0 = M.foldWithKey setMeta doc metadata diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index b303fa7d7..be34641a9 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 @@ -227,6 +231,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/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs new file mode 100644 index 000000000..8d8af309e --- /dev/null +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -0,0 +1,547 @@ +{-# 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 inp out = do + curDate <- formatTime defaultTimeLocale "%F" <$> getZonedTime + let getModTime = formatTime defaultTimeLocale "%F" + <$> getModificationTime inp + curMtime <- catchIOError getModTime (const (return "")) + + return $ T2TMeta curDate curMtime inp 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/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/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/test-pandoc.hs b/tests/test-pandoc.hs index c07a51ec5..1dab8e6f1 100644 --- a/tests/test-pandoc.hs +++ b/tests/test-pandoc.hs @@ -10,6 +10,7 @@ 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 @@ -40,7 +41,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. |