Implemented SoftBreak and new --wrap
option.
Added threefold wrapping option. * Command line option: deprecated `--no-wrap`, added `--wrap=[auto|none|preserve]` * Added WrapOption, exported from Text.Pandoc.Options * Changed type of writerWrapText in WriterOptions from Bool to WrapOption. * Modified Text.Pandoc.Shared functions for SoftBreak. * Supported SoftBreak in writers. * Updated tests. * Updated README. Closes #1701.
This commit is contained in:
parent
63d875c6cb
commit
536b6bf538
50 changed files with 323 additions and 171 deletions
15
README
15
README
|
@ -522,11 +522,20 @@ General writer options
|
|||
to inch/centimeters and vice versa. The default is 96dpi.
|
||||
Technically, the correct term would be ppi (pixels per inch).
|
||||
|
||||
`--wrap=[auto|none|preserve]`
|
||||
|
||||
: Determine how text is wrapped in the output (the source
|
||||
code, not the rendered version). With `auto` (the default),
|
||||
pandoc will attempt to wrap lines to the column width specified by
|
||||
`--columns` (default 80). With `none`, pandoc will not wrap
|
||||
lines at all. With `preserve`, pandoc will attempt to
|
||||
preserve the wrapping from the source document (that is,
|
||||
where there are nonsemantic newlines in the source, there
|
||||
will be nonsemantic newlines in the output as well).
|
||||
|
||||
`--no-wrap`
|
||||
|
||||
: Disable text wrapping in output. By default, text is wrapped
|
||||
appropriately for the output format. This affects only the
|
||||
generated source code, not the layout on the rendered page.
|
||||
: Deprecated synonym for `--wrap=none`.
|
||||
|
||||
`--columns=`*NUMBER*
|
||||
|
||||
|
|
|
@ -100,6 +100,10 @@ function Space()
|
|||
return " "
|
||||
end
|
||||
|
||||
function SoftBreak()
|
||||
return "\n"
|
||||
end
|
||||
|
||||
function LineBreak()
|
||||
return "<br/>"
|
||||
end
|
||||
|
@ -128,12 +132,12 @@ function Strikeout(s)
|
|||
return '<del>' .. s .. '</del>'
|
||||
end
|
||||
|
||||
function Link(s, src, tit)
|
||||
function Link(s, src, tit, attr)
|
||||
return "<a href='" .. escape(src,true) .. "' title='" ..
|
||||
escape(tit,true) .. "'>" .. s .. "</a>"
|
||||
end
|
||||
|
||||
function Image(s, src, tit)
|
||||
function Image(s, src, tit, attr)
|
||||
return "<img src='" .. escape(src,true) .. "' title='" ..
|
||||
escape(tit,true) .. "'/>"
|
||||
end
|
||||
|
|
25
pandoc.hs
25
pandoc.hs
|
@ -48,7 +48,7 @@ import System.Environment ( getArgs, getProgName )
|
|||
import System.Exit ( ExitCode (..), exitSuccess )
|
||||
import System.FilePath
|
||||
import System.Console.GetOpt
|
||||
import Data.Char ( toLower )
|
||||
import Data.Char ( toLower, toUpper )
|
||||
import Data.List ( delete, intercalate, isPrefixOf, isSuffixOf, sort )
|
||||
import System.Directory ( getAppUserDataDirectory, findExecutable,
|
||||
doesFileExist, Permissions(..), getPermissions )
|
||||
|
@ -197,7 +197,7 @@ data Opt = Opt
|
|||
, optVerbose :: Bool -- ^ Verbose diagnostic output
|
||||
, optReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
|
||||
, optDpi :: Int -- ^ Dpi
|
||||
, optWrapText :: Bool -- ^ Wrap text
|
||||
, optWrapText :: WrapOption -- ^ Options for wrapping text
|
||||
, optColumns :: Int -- ^ Line length in characters
|
||||
, optFilters :: [FilePath] -- ^ Filters to apply
|
||||
, optEmailObfuscation :: ObfuscationMethod
|
||||
|
@ -260,7 +260,7 @@ defaultOpts = Opt
|
|||
, optVerbose = False
|
||||
, optReferenceLinks = False
|
||||
, optDpi = 96
|
||||
, optWrapText = True
|
||||
, optWrapText = WrapAuto
|
||||
, optColumns = 72
|
||||
, optFilters = []
|
||||
, optEmailObfuscation = JavascriptObfuscation
|
||||
|
@ -468,8 +468,19 @@ options =
|
|||
|
||||
, Option "" ["no-wrap"]
|
||||
(NoArg
|
||||
(\opt -> return opt { optWrapText = False }))
|
||||
"" -- "Do not wrap text in output"
|
||||
(\opt -> do warn $ "--no-wrap is deprecated. " ++
|
||||
"Use --wrap=none or --wrap=preserve instead."
|
||||
return opt { optWrapText = WrapNone }))
|
||||
""
|
||||
|
||||
, Option "" ["wrap"]
|
||||
(ReqArg
|
||||
(\arg opt ->
|
||||
case safeRead ("Wrap" ++ uppercaseFirstLetter arg) of
|
||||
Just o -> return opt { optWrapText = o }
|
||||
Nothing -> err 77 "--wrap must be auto, none, or preserve")
|
||||
"[auto|none|preserve]")
|
||||
"" -- "Option for wrapping text in output"
|
||||
|
||||
, Option "" ["columns"]
|
||||
(ReqArg
|
||||
|
@ -1051,6 +1062,10 @@ applyFilters :: [FilePath] -> [String] -> Pandoc -> IO Pandoc
|
|||
applyFilters filters args d =
|
||||
foldrM ($) d $ map (flip externalFilter args) filters
|
||||
|
||||
uppercaseFirstLetter :: String -> String
|
||||
uppercaseFirstLetter (c:cs) = toUpper c : cs
|
||||
uppercaseFirstLetter [] = []
|
||||
|
||||
main :: IO ()
|
||||
main = do
|
||||
|
||||
|
|
|
@ -42,6 +42,7 @@ module Text.Pandoc.Options ( Extension(..)
|
|||
, ObfuscationMethod (..)
|
||||
, HTMLSlideVariant (..)
|
||||
, EPUBVersion (..)
|
||||
, WrapOption (..)
|
||||
, WriterOptions (..)
|
||||
, TrackChanges (..)
|
||||
, def
|
||||
|
@ -322,6 +323,12 @@ data TrackChanges = AcceptChanges
|
|||
| AllChanges
|
||||
deriving (Show, Read, Eq, Data, Typeable, Generic)
|
||||
|
||||
-- | Options for wrapping text in the output.
|
||||
data WrapOption = WrapAuto -- ^ Automatically wrap to width
|
||||
| WrapNone -- ^ No non-semantic newlines
|
||||
| WrapPreserve -- ^ Preserve wrapping of input source
|
||||
deriving (Show, Read, Eq, Data, Typeable, Generic)
|
||||
|
||||
-- | Options for writers
|
||||
data WriterOptions = WriterOptions
|
||||
{ writerStandalone :: Bool -- ^ Include header and footer
|
||||
|
@ -339,7 +346,7 @@ data WriterOptions = WriterOptions
|
|||
, writerExtensions :: Set Extension -- ^ Markdown extensions that can be used
|
||||
, writerReferenceLinks :: Bool -- ^ Use reference links in writing markdown, rst
|
||||
, writerDpi :: Int -- ^ Dpi for pixel to/from inch/cm conversions
|
||||
, writerWrapText :: Bool -- ^ Wrap text to line length
|
||||
, writerWrapText :: WrapOption -- ^ Option for wrapping text
|
||||
, writerColumns :: Int -- ^ Characters in a line (for text wrapping)
|
||||
, writerEmailObfuscation :: ObfuscationMethod -- ^ How to obfuscate emails
|
||||
, writerIdentifierPrefix :: String -- ^ Prefix for section & note ids in HTML
|
||||
|
@ -386,7 +393,7 @@ instance Default WriterOptions where
|
|||
, writerExtensions = pandocExtensions
|
||||
, writerReferenceLinks = False
|
||||
, writerDpi = 96
|
||||
, writerWrapText = True
|
||||
, writerWrapText = WrapAuto
|
||||
, writerColumns = 72
|
||||
, writerEmailObfuscation = JavascriptObfuscation
|
||||
, writerIdentifierPrefix = ""
|
||||
|
|
|
@ -1679,7 +1679,7 @@ endline = try $ do
|
|||
(eof >> return mempty)
|
||||
<|> (guardEnabled Ext_hard_line_breaks >> return (return B.linebreak))
|
||||
<|> (guardEnabled Ext_ignore_line_breaks >> return mempty)
|
||||
<|> (return $ return B.softbreak)
|
||||
<|> (skipMany spaceChar >> return (return B.softbreak))
|
||||
|
||||
--
|
||||
-- links
|
||||
|
|
|
@ -375,17 +375,19 @@ isSpaceOrEmpty (Str "") = True
|
|||
isSpaceOrEmpty _ = False
|
||||
|
||||
-- | Extract the leading and trailing spaces from inside an inline element
|
||||
-- and place them outside the element.
|
||||
|
||||
-- and place them outside the element. SoftBreaks count as Spaces for
|
||||
-- these purposes.
|
||||
extractSpaces :: (Inlines -> Inlines) -> Inlines -> Inlines
|
||||
extractSpaces f is =
|
||||
let contents = B.unMany is
|
||||
left = case viewl contents of
|
||||
(Space :< _) -> B.space
|
||||
_ -> mempty
|
||||
(Space :< _) -> B.space
|
||||
(SoftBreak :< _) -> B.softbreak
|
||||
_ -> mempty
|
||||
right = case viewr contents of
|
||||
(_ :> Space) -> B.space
|
||||
_ -> mempty in
|
||||
(_ :> Space) -> B.space
|
||||
(_ :> SoftBreak) -> B.softbreak
|
||||
_ -> mempty in
|
||||
(left <> f (B.trimInlines . B.Many $ contents) <> right)
|
||||
|
||||
-- | Normalize @Pandoc@ document, consolidating doubled 'Space's,
|
||||
|
@ -452,6 +454,8 @@ normalizeInlines (Str x : ys) =
|
|||
isStr _ = False
|
||||
fromStr (Str z) = z
|
||||
fromStr _ = error "normalizeInlines - fromStr - not a Str"
|
||||
normalizeInlines (Space : SoftBreak : ys) =
|
||||
SoftBreak : normalizeInlines ys
|
||||
normalizeInlines (Space : ys) =
|
||||
if null rest
|
||||
then []
|
||||
|
@ -539,6 +543,7 @@ removeFormatting = query go . walk deNote
|
|||
where go :: Inline -> [Inline]
|
||||
go (Str xs) = [Str xs]
|
||||
go Space = [Space]
|
||||
go SoftBreak = [SoftBreak]
|
||||
go (Code _ x) = [Str x]
|
||||
go (Math _ x) = [Str x]
|
||||
go LineBreak = [Space]
|
||||
|
@ -553,6 +558,7 @@ stringify :: Walkable Inline a => a -> String
|
|||
stringify = query go . walk deNote
|
||||
where go :: Inline -> [Char]
|
||||
go Space = " "
|
||||
go SoftBreak = " "
|
||||
go (Str x) = x
|
||||
go (Code _ x) = x
|
||||
go (Math _ x) = x
|
||||
|
|
|
@ -73,7 +73,7 @@ pandocToAsciiDoc :: WriterOptions -> Pandoc -> State WriterState String
|
|||
pandocToAsciiDoc opts (Pandoc meta blocks) = do
|
||||
let titleblock = not $ null (docTitle meta) && null (docAuthors meta) &&
|
||||
null (docDate meta)
|
||||
let colwidth = if writerWrapText opts
|
||||
let colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
metadata <- metaToJSON opts
|
||||
|
@ -227,7 +227,7 @@ blockToAsciiDoc opts (Table caption aligns widths headers rows) = do
|
|||
rows' <- mapM makeRow rows
|
||||
head' <- makeRow headers
|
||||
let head'' = if all null headers then empty else head'
|
||||
let colwidth = if writerWrapText opts
|
||||
let colwidth = if writerWrapText opts == WrapAuto
|
||||
then writerColumns opts
|
||||
else 100000
|
||||
let maxwidth = maximum $ map offset (head':rows')
|
||||
|
@ -335,7 +335,7 @@ inlineListToAsciiDoc opts lst = do
|
|||
x' <- withIntraword $ inlineToAsciiDoc opts x
|
||||
xs' <- go xs
|
||||
return (y' <> x' <> xs')
|
||||
| x /= Space && x /= LineBreak = do
|
||||
| not (isSpacy x) = do
|
||||
y' <- withIntraword $ inlineToAsciiDoc opts y
|
||||
xs' <- go (x:xs)
|
||||
return (y' <> xs')
|
||||
|
@ -345,6 +345,7 @@ inlineListToAsciiDoc opts lst = do
|
|||
return (x' <> xs')
|
||||
isSpacy Space = True
|
||||
isSpacy LineBreak = True
|
||||
isSpacy SoftBreak = True
|
||||
isSpacy _ = False
|
||||
|
||||
setIntraword :: Bool -> State WriterState ()
|
||||
|
@ -391,6 +392,11 @@ inlineToAsciiDoc _ (RawInline f s)
|
|||
| otherwise = return empty
|
||||
inlineToAsciiDoc _ (LineBreak) = return $ " +" <> cr
|
||||
inlineToAsciiDoc _ Space = return space
|
||||
inlineToAsciiDoc opts SoftBreak =
|
||||
case writerWrapText opts of
|
||||
WrapAuto -> return space
|
||||
WrapPreserve -> return cr
|
||||
WrapNone -> return space
|
||||
inlineToAsciiDoc opts (Cite _ lst) = inlineListToAsciiDoc opts lst
|
||||
inlineToAsciiDoc opts (Link _ txt (src, _tit)) = do
|
||||
-- relative: link:downloads/foo.zip[download foo.zip]
|
||||
|
|
|
@ -75,7 +75,7 @@ blocksToCommonMark opts bs = return $
|
|||
T.unpack $ nodeToCommonmark cmarkOpts colwidth
|
||||
$ node DOCUMENT (blocksToNodes bs)
|
||||
where cmarkOpts = [optHardBreaks | isEnabled Ext_hard_line_breaks opts]
|
||||
colwidth = if writerWrapText opts
|
||||
colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
|
||||
|
@ -84,7 +84,7 @@ inlinesToCommonMark opts ils = return $
|
|||
T.unpack $ nodeToCommonmark cmarkOpts colwidth
|
||||
$ node PARAGRAPH (inlinesToNodes ils)
|
||||
where cmarkOpts = [optHardBreaks | isEnabled Ext_hard_line_breaks opts]
|
||||
colwidth = if writerWrapText opts
|
||||
colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
|
||||
|
@ -138,6 +138,7 @@ inlineToNodes :: Inline -> [Node] -> [Node]
|
|||
inlineToNodes (Str s) = (node (TEXT (T.pack s)) [] :)
|
||||
inlineToNodes Space = (node (TEXT (T.pack " ")) [] :)
|
||||
inlineToNodes LineBreak = (node LINEBREAK [] :)
|
||||
inlineToNodes SoftBreak = (node SOFTBREAK [] :)
|
||||
inlineToNodes (Emph xs) = (node EMPH (inlinesToNodes xs) :)
|
||||
inlineToNodes (Strong xs) = (node STRONG (inlinesToNodes xs) :)
|
||||
inlineToNodes (Strikeout xs) =
|
||||
|
|
|
@ -63,7 +63,7 @@ writeConTeXt options document =
|
|||
|
||||
pandocToConTeXt :: WriterOptions -> Pandoc -> State WriterState String
|
||||
pandocToConTeXt options (Pandoc meta blocks) = do
|
||||
let colwidth = if writerWrapText options
|
||||
let colwidth = if writerWrapText options == WrapAuto
|
||||
then Just $ writerColumns options
|
||||
else Nothing
|
||||
metadata <- metaToJSON options
|
||||
|
@ -315,6 +315,12 @@ inlineToConTeXt (RawInline "context" str) = return $ text str
|
|||
inlineToConTeXt (RawInline "tex" str) = return $ text str
|
||||
inlineToConTeXt (RawInline _ _) = return empty
|
||||
inlineToConTeXt (LineBreak) = return $ text "\\crlf" <> cr
|
||||
inlineToConTeXt SoftBreak = do
|
||||
wrapText <- gets (writerWrapText . stOptions)
|
||||
return $ case wrapText of
|
||||
WrapAuto -> space
|
||||
WrapNone -> space
|
||||
WrapPreserve -> cr
|
||||
inlineToConTeXt Space = return space
|
||||
-- Handle HTML-like internal document references to sections
|
||||
inlineToConTeXt (Link _ txt (('#' : ref), _)) = do
|
||||
|
|
|
@ -276,6 +276,8 @@ inlineToCustom lua (Str str) = callfunc lua "Str" str
|
|||
|
||||
inlineToCustom lua Space = callfunc lua "Space"
|
||||
|
||||
inlineToCustom lua SoftBreak = callfunc lua "SoftBreak"
|
||||
|
||||
inlineToCustom lua (Emph lst) = callfunc lua "Emph" lst
|
||||
|
||||
inlineToCustom lua (Strong lst) = callfunc lua "Strong" lst
|
||||
|
@ -308,11 +310,11 @@ inlineToCustom lua (RawInline format str) =
|
|||
|
||||
inlineToCustom lua (LineBreak) = callfunc lua "LineBreak"
|
||||
|
||||
inlineToCustom lua (Link _ txt (src,tit)) =
|
||||
callfunc lua "Link" txt src tit
|
||||
inlineToCustom lua (Link attr txt (src,tit)) =
|
||||
callfunc lua "Link" txt src tit (attrToMap attr)
|
||||
|
||||
inlineToCustom lua (Image _ alt (src,tit)) =
|
||||
callfunc lua "Image" alt src tit
|
||||
inlineToCustom lua (Image attr alt (src,tit)) =
|
||||
callfunc lua "Image" alt src tit (attrToMap attr)
|
||||
|
||||
inlineToCustom lua (Note contents) = callfunc lua "Note" contents
|
||||
|
||||
|
|
|
@ -52,7 +52,7 @@ import Data.Generics (everywhere, mkT)
|
|||
authorToDocbook :: WriterOptions -> [Inline] -> B.Inlines
|
||||
authorToDocbook opts name' =
|
||||
let name = render Nothing $ inlinesToDocbook opts name'
|
||||
colwidth = if writerWrapText opts
|
||||
colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
in B.rawInline "docbook" $ render colwidth $
|
||||
|
@ -76,7 +76,7 @@ authorToDocbook opts name' =
|
|||
writeDocbook :: WriterOptions -> Pandoc -> String
|
||||
writeDocbook opts (Pandoc meta blocks) =
|
||||
let elements = hierarchicalize blocks
|
||||
colwidth = if writerWrapText opts
|
||||
colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
render' = render colwidth
|
||||
|
@ -331,6 +331,8 @@ inlineToDocbook _ (RawInline f x) | f == "html" || f == "docbook" = text x
|
|||
| otherwise = empty
|
||||
inlineToDocbook _ LineBreak = text "\n"
|
||||
inlineToDocbook _ Space = space
|
||||
-- because we use \n for LineBreak, we can't do soft breaks:
|
||||
inlineToDocbook _ SoftBreak = space
|
||||
inlineToDocbook opts (Link attr txt (src, _))
|
||||
| Just email <- stripPrefix "mailto:" src =
|
||||
let emailLink = inTagsSimple "email" $ text $
|
||||
|
|
|
@ -245,7 +245,7 @@ writeDocx opts doc@(Pandoc meta _) = do
|
|||
let tocTitle = fromMaybe (stTocTitle defaultWriterState) $
|
||||
metaValueToInlines <$> lookupMeta "toc-title" meta
|
||||
|
||||
((contents, footnotes), st) <- runStateT (writeOpenXML opts{writerWrapText = False} doc')
|
||||
((contents, footnotes), st) <- runStateT (writeOpenXML opts{writerWrapText = WrapAuto} doc')
|
||||
defaultWriterState{ stChangesAuthor = fromMaybe "unknown" username
|
||||
, stChangesDate = formatTime defaultTimeLocale "%FT%XZ" utctime
|
||||
, stPrintWidth = (maybe 420 (\x -> quot x 20) pgContentWidth)
|
||||
|
@ -981,6 +981,7 @@ setFirstPara = modify $ \s -> s { stFirstPara = True }
|
|||
inlineToOpenXML :: WriterOptions -> Inline -> WS [Element]
|
||||
inlineToOpenXML _ (Str str) = formattedString str
|
||||
inlineToOpenXML opts Space = inlineToOpenXML opts (Str " ")
|
||||
inlineToOpenXML opts SoftBreak = inlineToOpenXML opts (Str " ")
|
||||
inlineToOpenXML opts (Span (_,classes,kvs) ils)
|
||||
| "insertion" `elem` classes = do
|
||||
defaultAuthor <- gets stChangesAuthor
|
||||
|
|
|
@ -43,7 +43,8 @@ import Text.Pandoc.Definition
|
|||
import Text.Pandoc.Options ( WriterOptions(
|
||||
writerTableOfContents
|
||||
, writerStandalone
|
||||
, writerTemplate) )
|
||||
, writerTemplate
|
||||
, writerWrapText), WrapOption(..) )
|
||||
import Text.Pandoc.Shared ( escapeURI, removeFormatting, camelCaseToHyphenated
|
||||
, trimr, normalize, substitute )
|
||||
import Text.Pandoc.Writers.Shared ( defField, metaToJSON )
|
||||
|
@ -461,6 +462,12 @@ inlineToDokuWiki _ (RawInline f str)
|
|||
|
||||
inlineToDokuWiki _ (LineBreak) = return "\\\\\n"
|
||||
|
||||
inlineToDokuWiki opts SoftBreak =
|
||||
case writerWrapText opts of
|
||||
WrapNone -> return " "
|
||||
WrapAuto -> return " "
|
||||
WrapPreserve -> return "\n"
|
||||
|
||||
inlineToDokuWiki _ Space = return " "
|
||||
|
||||
inlineToDokuWiki opts (Link _ txt (src, _)) = do
|
||||
|
|
|
@ -50,6 +50,7 @@ import Text.Pandoc.Shared ( renderTags', safeRead, uniqueIdent, trim
|
|||
import qualified Text.Pandoc.Shared as S (Element(..))
|
||||
import Text.Pandoc.Builder (fromList, setMeta)
|
||||
import Text.Pandoc.Options ( WriterOptions(..)
|
||||
, WrapOption(..)
|
||||
, HTMLMathMethod(..)
|
||||
, EPUBVersion(..)
|
||||
, ObfuscationMethod(NoObfuscation) )
|
||||
|
@ -350,7 +351,7 @@ writeEPUB opts doc@(Pandoc meta _) = do
|
|||
if epub3
|
||||
then MathML Nothing
|
||||
else writerHTMLMathMethod opts
|
||||
, writerWrapText = True }
|
||||
, writerWrapText = WrapAuto }
|
||||
metadata <- getEPUBMetadata opts' meta
|
||||
|
||||
-- cover page
|
||||
|
|
|
@ -27,7 +27,7 @@ FictionBook is an XML-based e-book format. For more information see:
|
|||
-}
|
||||
module Text.Pandoc.Writers.FB2 (writeFB2) where
|
||||
|
||||
import Control.Monad.State (StateT, evalStateT, get, modify)
|
||||
import Control.Monad.State (StateT, evalStateT, get, gets, modify)
|
||||
import Control.Monad.State (liftM, liftM2, liftIO)
|
||||
import Data.ByteString.Base64 (encode)
|
||||
import Data.Char (toLower, isSpace, isAscii, isControl)
|
||||
|
@ -439,6 +439,7 @@ toXml (Quoted DoubleQuote ss) = do
|
|||
toXml (Cite _ ss) = cMapM toXml ss -- FIXME: support citation styles
|
||||
toXml (Code _ s) = return [el "code" s]
|
||||
toXml Space = return [txt " "]
|
||||
toXml SoftBreak = return [txt " "]
|
||||
toXml LineBreak = return [el "empty-line" ()]
|
||||
toXml (Math _ formula) = insertMath InlineImage formula
|
||||
toXml (RawInline _ _) = return [] -- raw TeX and raw HTML are suppressed
|
||||
|
|
|
@ -95,9 +95,9 @@ strToHtml [] = ""
|
|||
|
||||
-- | Hard linebreak.
|
||||
nl :: WriterOptions -> Html
|
||||
nl opts = if writerWrapText opts
|
||||
then preEscapedString "\n"
|
||||
else mempty
|
||||
nl opts = if writerWrapText opts == WrapNone
|
||||
then mempty
|
||||
else preEscapedString "\n"
|
||||
|
||||
-- | Convert Pandoc document to Html string.
|
||||
writeHtmlString :: WriterOptions -> Pandoc -> String
|
||||
|
@ -697,6 +697,10 @@ inlineToHtml opts inline =
|
|||
case inline of
|
||||
(Str str) -> return $ strToHtml str
|
||||
(Space) -> return $ strToHtml " "
|
||||
(SoftBreak) -> return $ case writerWrapText opts of
|
||||
WrapNone -> preEscapedString " "
|
||||
WrapAuto -> preEscapedString " "
|
||||
WrapPreserve -> preEscapedString "\n"
|
||||
(LineBreak) -> return $ (if writerHtml5 opts then H5.br else H.br)
|
||||
<> strToHtml "\n"
|
||||
(Span (id',classes,kvs) ils)
|
||||
|
|
|
@ -57,7 +57,7 @@ writeHaddock opts document =
|
|||
-- | Return haddock representation of document.
|
||||
pandocToHaddock :: WriterOptions -> Pandoc -> State WriterState String
|
||||
pandocToHaddock opts (Pandoc meta blocks) = do
|
||||
let colwidth = if writerWrapText opts
|
||||
let colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
body <- blockListToHaddock opts blocks
|
||||
|
@ -325,6 +325,11 @@ inlineToHaddock _ (RawInline f str)
|
|||
| otherwise = return empty
|
||||
-- no line break in haddock (see above on CodeBlock)
|
||||
inlineToHaddock _ (LineBreak) = return cr
|
||||
inlineToHaddock opts SoftBreak =
|
||||
case writerWrapText opts of
|
||||
WrapAuto -> return space
|
||||
WrapNone -> return space
|
||||
WrapPreserve -> return cr
|
||||
inlineToHaddock _ Space = return space
|
||||
inlineToHaddock opts (Cite _ lst) = inlineListToHaddock opts lst
|
||||
inlineToHaddock _ (Link _ txt (src, _)) = do
|
||||
|
|
|
@ -122,7 +122,7 @@ citeName = "Cite"
|
|||
-- | Convert Pandoc document to string in ICML format.
|
||||
writeICML :: WriterOptions -> Pandoc -> IO String
|
||||
writeICML opts (Pandoc meta blocks) = do
|
||||
let colwidth = if writerWrapText opts
|
||||
let colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
render' = render colwidth
|
||||
|
@ -414,6 +414,11 @@ inlineToICML opts style (Quoted DoubleQuote lst) = inlinesToICML opts style $ [S
|
|||
inlineToICML opts style (Cite _ lst) = inlinesToICML opts (citeName:style) lst
|
||||
inlineToICML _ style (Code _ str) = charStyle (codeName:style) $ text $ escapeStringForXML str
|
||||
inlineToICML _ style Space = charStyle style space
|
||||
inlineToICML opts style SoftBreak =
|
||||
case writerWrapText opts of
|
||||
WrapAuto -> charStyle style space
|
||||
WrapNone -> charStyle style space
|
||||
WrapPreserve -> charStyle style cr
|
||||
inlineToICML _ style LineBreak = charStyle style $ text lineSeparator
|
||||
inlineToICML opts style (Math mt str) =
|
||||
cat <$> mapM (inlineToICML opts style) (texMathToInlines mt str)
|
||||
|
@ -449,12 +454,18 @@ footnoteToICML opts style lst =
|
|||
|
||||
-- | Auxiliary function to merge Space elements into the adjacent Strs.
|
||||
mergeSpaces :: [Inline] -> [Inline]
|
||||
mergeSpaces ((Str s):(Space:((Str s'):xs))) = mergeSpaces $ Str(s++" "++s') : xs
|
||||
mergeSpaces (Space:((Str s):xs)) = mergeSpaces $ Str (" "++s) : xs
|
||||
mergeSpaces ((Str s):(Space:xs)) = mergeSpaces $ Str (s++" ") : xs
|
||||
mergeSpaces ((Str s):(x:((Str s'):xs))) | isSp x =
|
||||
mergeSpaces $ Str(s++" "++s') : xs
|
||||
mergeSpaces (x:((Str s):xs)) | isSp x = mergeSpaces $ Str (" "++s) : xs
|
||||
mergeSpaces ((Str s):(x:xs)) | isSp x = mergeSpaces $ Str (s++" ") : xs
|
||||
mergeSpaces (x:xs) = x : (mergeSpaces xs)
|
||||
mergeSpaces [] = []
|
||||
|
||||
isSp :: Inline -> Bool
|
||||
isSp Space = True
|
||||
isSp SoftBreak = True
|
||||
isSp _ = False
|
||||
|
||||
-- | Wrap a list of inline elements in an ICML Paragraph Style
|
||||
parStyle :: WriterOptions -> Style -> [Inline] -> WS Doc
|
||||
parStyle opts style lst =
|
||||
|
|
|
@ -105,7 +105,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do
|
|||
modify $ \s -> s{ stInternalLinks = query isInternalLink blocks' }
|
||||
let template = writerTemplate options
|
||||
-- set stBook depending on documentclass
|
||||
let colwidth = if writerWrapText options
|
||||
let colwidth = if writerWrapText options == WrapAuto
|
||||
then Just $ writerColumns options
|
||||
else Nothing
|
||||
metadata <- metaToJSON options
|
||||
|
@ -357,6 +357,7 @@ isListBlock _ = False
|
|||
|
||||
isLineBreakOrSpace :: Inline -> Bool
|
||||
isLineBreakOrSpace LineBreak = True
|
||||
isLineBreakOrSpace SoftBreak = True
|
||||
isLineBreakOrSpace Space = True
|
||||
isLineBreakOrSpace _ = False
|
||||
|
||||
|
@ -896,6 +897,12 @@ inlineToLaTeX (RawInline f str)
|
|||
= return $ text str
|
||||
| otherwise = return empty
|
||||
inlineToLaTeX (LineBreak) = return $ "\\\\" <> cr
|
||||
inlineToLaTeX SoftBreak = do
|
||||
wrapText <- gets (writerWrapText . stOptions)
|
||||
case wrapText of
|
||||
WrapAuto -> return space
|
||||
WrapNone -> return space
|
||||
WrapPreserve -> return cr
|
||||
inlineToLaTeX Space = return space
|
||||
inlineToLaTeX (Link _ txt ('#':ident, _)) = do
|
||||
contents <- inlineListToLaTeX txt
|
||||
|
|
|
@ -54,7 +54,7 @@ writeMan opts document = evalState (pandocToMan opts document) (WriterState [] F
|
|||
-- | Return groff man representation of document.
|
||||
pandocToMan :: WriterOptions -> Pandoc -> State WriterState String
|
||||
pandocToMan opts (Pandoc meta blocks) = do
|
||||
let colwidth = if writerWrapText opts
|
||||
let colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
let render' = render colwidth
|
||||
|
@ -146,6 +146,7 @@ breakSentence xs =
|
|||
[] -> (as, [])
|
||||
[c] -> (as ++ [c], [])
|
||||
(c:Space:cs) -> (as ++ [c], cs)
|
||||
(c:SoftBreak:cs) -> (as ++ [c], cs)
|
||||
(Str ".":Str (')':ys):cs) -> (as ++ [Str ".", Str (')':ys)], cs)
|
||||
(x@(Str ('.':')':_)):cs) -> (as ++ [x], cs)
|
||||
(LineBreak:x@(Str ('.':_)):cs) -> (as ++[LineBreak], x:cs)
|
||||
|
@ -343,6 +344,7 @@ inlineToMan _ (RawInline f str)
|
|||
| otherwise = return empty
|
||||
inlineToMan _ (LineBreak) = return $
|
||||
cr <> text ".PD 0" $$ text ".P" $$ text ".PD" <> cr
|
||||
inlineToMan _ SoftBreak = return space
|
||||
inlineToMan _ Space = return space
|
||||
inlineToMan opts (Link _ txt (src, _)) = do
|
||||
linktext <- inlineListToMan opts txt
|
||||
|
|
|
@ -71,8 +71,9 @@ instance Default WriterState
|
|||
writeMarkdown :: WriterOptions -> Pandoc -> String
|
||||
writeMarkdown opts document =
|
||||
evalState (pandocToMarkdown opts{
|
||||
writerWrapText = writerWrapText opts &&
|
||||
not (isEnabled Ext_hard_line_breaks opts) }
|
||||
writerWrapText = if isEnabled Ext_hard_line_breaks opts
|
||||
then WrapNone
|
||||
else writerWrapText opts }
|
||||
document) def
|
||||
|
||||
-- | Convert Pandoc to plain text (like markdown, but without links,
|
||||
|
@ -144,7 +145,7 @@ jsonToYaml _ = empty
|
|||
-- | Return markdown representation of document.
|
||||
pandocToMarkdown :: WriterOptions -> Pandoc -> State WriterState String
|
||||
pandocToMarkdown opts (Pandoc meta blocks) = do
|
||||
let colwidth = if writerWrapText opts
|
||||
let colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
isPlain <- gets stPlain
|
||||
|
@ -324,7 +325,7 @@ blockToMarkdown opts (Plain inlines) = do
|
|||
contents <- inlineListToMarkdown opts inlines
|
||||
-- escape if para starts with ordered list marker
|
||||
st <- get
|
||||
let colwidth = if writerWrapText opts
|
||||
let colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
let rendered = render colwidth contents
|
||||
|
@ -708,6 +709,10 @@ inlineListToMarkdown opts lst = do
|
|||
Space:(Str('[':_)):_ -> unshortcutable
|
||||
Space:(RawInline _ ('[':_)):_ -> unshortcutable
|
||||
Space:(Cite _ _):_ -> unshortcutable
|
||||
SoftBreak:(Link _ _ _):_ -> unshortcutable
|
||||
SoftBreak:(Str('[':_)):_ -> unshortcutable
|
||||
SoftBreak:(RawInline _ ('[':_)):_ -> unshortcutable
|
||||
SoftBreak:(Cite _ _):_ -> unshortcutable
|
||||
(Cite _ _):_ -> unshortcutable
|
||||
Str ('[':_):_ -> unshortcutable
|
||||
(RawInline _ ('[':_)):_ -> unshortcutable
|
||||
|
@ -721,18 +726,25 @@ inlineListToMarkdown opts lst = do
|
|||
modify (\s -> s {stRefShortcutable = True })
|
||||
fmap (iMark <>) (go is)
|
||||
|
||||
isSp :: Inline -> Bool
|
||||
isSp Space = True
|
||||
isSp SoftBreak = True
|
||||
isSp _ = False
|
||||
|
||||
avoidBadWrapsInList :: [Inline] -> [Inline]
|
||||
avoidBadWrapsInList [] = []
|
||||
avoidBadWrapsInList (Space:Str ('>':cs):xs) =
|
||||
avoidBadWrapsInList (s:Str ('>':cs):xs) | isSp s =
|
||||
Str (' ':'>':cs) : avoidBadWrapsInList xs
|
||||
avoidBadWrapsInList (Space:Str [c]:[])
|
||||
| c `elem` ['-','*','+'] = Str [' ', c] : []
|
||||
avoidBadWrapsInList (Space:Str [c]:Space:xs)
|
||||
| c `elem` ['-','*','+'] = Str [' ', c] : Space : avoidBadWrapsInList xs
|
||||
avoidBadWrapsInList (Space:Str cs:Space:xs)
|
||||
| isOrderedListMarker cs = Str (' ':cs) : Space : avoidBadWrapsInList xs
|
||||
avoidBadWrapsInList (Space:Str cs:[])
|
||||
| isOrderedListMarker cs = Str (' ':cs) : []
|
||||
avoidBadWrapsInList (s:Str [c]:[])
|
||||
| isSp s && c `elem` ['-','*','+'] = Str [' ', c] : []
|
||||
avoidBadWrapsInList (s:Str [c]:Space:xs)
|
||||
| isSp s && c `elem` ['-','*','+'] =
|
||||
Str [' ', c] : Space : avoidBadWrapsInList xs
|
||||
avoidBadWrapsInList (s:Str cs:Space:xs)
|
||||
| isSp s && isOrderedListMarker cs =
|
||||
Str (' ':cs) : Space : avoidBadWrapsInList xs
|
||||
avoidBadWrapsInList (s:Str cs:[])
|
||||
| isSp s && isOrderedListMarker cs = Str (' ':cs) : []
|
||||
avoidBadWrapsInList (x:xs) = x : avoidBadWrapsInList xs
|
||||
|
||||
isOrderedListMarker :: String -> Bool
|
||||
|
@ -747,6 +759,7 @@ isRight (Left _) = False
|
|||
escapeSpaces :: Inline -> Inline
|
||||
escapeSpaces (Str s) = Str $ substitute " " "\\ " s
|
||||
escapeSpaces Space = Str "\\ "
|
||||
escapeSpaces SoftBreak = Str "\\ "
|
||||
escapeSpaces x = x
|
||||
|
||||
-- | Convert Pandoc inline element to markdown.
|
||||
|
@ -876,6 +889,11 @@ inlineToMarkdown opts (LineBreak) = do
|
|||
then "\\" <> cr
|
||||
else " " <> cr
|
||||
inlineToMarkdown _ Space = return space
|
||||
inlineToMarkdown opts SoftBreak = return $
|
||||
case writerWrapText opts of
|
||||
WrapNone -> space
|
||||
WrapAuto -> space
|
||||
WrapPreserve -> cr
|
||||
inlineToMarkdown opts (Cite [] lst) = inlineListToMarkdown opts lst
|
||||
inlineToMarkdown opts (Cite (c:cs) lst)
|
||||
| not (isEnabled Ext_citations opts) = inlineListToMarkdown opts lst
|
||||
|
|
|
@ -397,6 +397,13 @@ inlineToMediaWiki (RawInline f str)
|
|||
|
||||
inlineToMediaWiki (LineBreak) = return "<br />\n"
|
||||
|
||||
inlineToMediaWiki SoftBreak = do
|
||||
wrapText <- gets (writerWrapText . stOptions)
|
||||
case wrapText of
|
||||
WrapAuto -> return " "
|
||||
WrapNone -> return " "
|
||||
WrapPreserve -> return "\n"
|
||||
|
||||
inlineToMediaWiki Space = return " "
|
||||
|
||||
inlineToMediaWiki (Link _ txt (src, _)) = do
|
||||
|
|
|
@ -34,7 +34,7 @@ metadata.
|
|||
-}
|
||||
module Text.Pandoc.Writers.Native ( writeNative )
|
||||
where
|
||||
import Text.Pandoc.Options ( WriterOptions(..) )
|
||||
import Text.Pandoc.Options ( WriterOptions(..), WrapOption(..) )
|
||||
import Data.List ( intersperse )
|
||||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Pretty
|
||||
|
@ -70,7 +70,7 @@ prettyBlock block = text $ show block
|
|||
-- | Prettyprint Pandoc document.
|
||||
writeNative :: WriterOptions -> Pandoc -> String
|
||||
writeNative opts (Pandoc meta blocks) =
|
||||
let colwidth = if writerWrapText opts
|
||||
let colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
withHead = if writerStandalone opts
|
||||
|
|
|
@ -37,7 +37,7 @@ import Text.TeXMath
|
|||
import qualified Data.ByteString.Lazy as B
|
||||
import Text.Pandoc.UTF8 ( fromStringLazy )
|
||||
import Codec.Archive.Zip
|
||||
import Text.Pandoc.Options ( WriterOptions(..) )
|
||||
import Text.Pandoc.Options ( WriterOptions(..), WrapOption(..) )
|
||||
import Text.Pandoc.Shared ( stringify, fetchItem', warn,
|
||||
getDefaultReferenceODT )
|
||||
import Text.Pandoc.ImageSize ( imageSize, desiredSizeInPoints )
|
||||
|
@ -67,7 +67,7 @@ writeODT opts doc@(Pandoc meta _) = do
|
|||
-- handle formulas and pictures
|
||||
picEntriesRef <- newIORef ([] :: [Entry])
|
||||
doc' <- walkM (transformPicMath opts picEntriesRef) $ walk fixDisplayMath doc
|
||||
let newContents = writeOpenDocument opts{writerWrapText = False} doc'
|
||||
let newContents = writeOpenDocument opts{writerWrapText = WrapAuto} doc'
|
||||
epochtime <- floor `fmap` getPOSIXTime
|
||||
let contentEntry = toEntry "content.xml" epochtime
|
||||
$ fromStringLazy newContents
|
||||
|
|
|
@ -45,7 +45,7 @@ import qualified Text.Pandoc.Builder as B
|
|||
writeOPML :: WriterOptions -> Pandoc -> String
|
||||
writeOPML opts (Pandoc meta blocks) =
|
||||
let elements = hierarchicalize blocks
|
||||
colwidth = if writerWrapText opts
|
||||
colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
meta' = B.setMeta "date" (B.str $ convertDate $ docDate meta) meta
|
||||
|
|
|
@ -175,7 +175,7 @@ handleSpaces s
|
|||
-- | Convert Pandoc document to string in OpenDocument format.
|
||||
writeOpenDocument :: WriterOptions -> Pandoc -> String
|
||||
writeOpenDocument opts (Pandoc meta blocks) =
|
||||
let colwidth = if writerWrapText opts
|
||||
let colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
render' = render colwidth
|
||||
|
@ -374,27 +374,31 @@ inlinesToOpenDocument o l = hcat <$> mapM (inlineToOpenDocument o) l
|
|||
-- | Convert an inline element to OpenDocument.
|
||||
inlineToOpenDocument :: WriterOptions -> Inline -> State WriterState Doc
|
||||
inlineToOpenDocument o ils
|
||||
| Space <- ils = inTextStyle space
|
||||
| Span _ xs <- ils = inlinesToOpenDocument o xs
|
||||
| LineBreak <- ils = return $ selfClosingTag "text:line-break" []
|
||||
| Str s <- ils = inTextStyle $ handleSpaces $ escapeStringForXML s
|
||||
| Emph l <- ils = withTextStyle Italic $ inlinesToOpenDocument o l
|
||||
| Strong l <- ils = withTextStyle Bold $ inlinesToOpenDocument o l
|
||||
| Strikeout l <- ils = withTextStyle Strike $ inlinesToOpenDocument o l
|
||||
| Superscript l <- ils = withTextStyle Sup $ inlinesToOpenDocument o l
|
||||
| Subscript l <- ils = withTextStyle Sub $ inlinesToOpenDocument o l
|
||||
| SmallCaps l <- ils = withTextStyle SmallC $ inlinesToOpenDocument o l
|
||||
| Quoted t l <- ils = inQuotes t <$> inlinesToOpenDocument o l
|
||||
| Code _ s <- ils = withTextStyle Pre $ inTextStyle $ preformatted s
|
||||
| Math t s <- ils = inlinesToOpenDocument o (texMathToInlines t s)
|
||||
| Cite _ l <- ils = inlinesToOpenDocument o l
|
||||
| RawInline f s <- ils = if f == Format "opendocument"
|
||||
then return $ text s
|
||||
else return empty
|
||||
| Link _ l (s,t) <- ils = mkLink s t <$> inlinesToOpenDocument o l
|
||||
| Image attr _ (s,t) <- ils = mkImg attr s t
|
||||
| Note l <- ils = mkNote l
|
||||
| otherwise = return empty
|
||||
= case ils of
|
||||
Space -> inTextStyle space
|
||||
SoftBreak
|
||||
| writerWrapText o == WrapPreserve
|
||||
-> inTextStyle (preformatted "\n")
|
||||
| otherwise -> inTextStyle space
|
||||
Span _ xs -> inlinesToOpenDocument o xs
|
||||
LineBreak -> return $ selfClosingTag "text:line-break" []
|
||||
Str s -> inTextStyle $ handleSpaces $ escapeStringForXML s
|
||||
Emph l -> withTextStyle Italic $ inlinesToOpenDocument o l
|
||||
Strong l -> withTextStyle Bold $ inlinesToOpenDocument o l
|
||||
Strikeout l -> withTextStyle Strike $ inlinesToOpenDocument o l
|
||||
Superscript l -> withTextStyle Sup $ inlinesToOpenDocument o l
|
||||
Subscript l -> withTextStyle Sub $ inlinesToOpenDocument o l
|
||||
SmallCaps l -> withTextStyle SmallC $ inlinesToOpenDocument o l
|
||||
Quoted t l -> inQuotes t <$> inlinesToOpenDocument o l
|
||||
Code _ s -> withTextStyle Pre $ inTextStyle $ preformatted s
|
||||
Math t s -> inlinesToOpenDocument o (texMathToInlines t s)
|
||||
Cite _ l -> inlinesToOpenDocument o l
|
||||
RawInline f s -> if f == Format "opendocument"
|
||||
then return $ text s
|
||||
else return empty
|
||||
Link _ l (s,t) -> mkLink s t <$> inlinesToOpenDocument o l
|
||||
Image attr _ (s,t) -> mkImg attr s t
|
||||
Note l -> mkNote l
|
||||
where
|
||||
preformatted s = handleSpaces $ escapeStringForXML s
|
||||
mkLink s t = inTags False "text:a" [ ("xlink:type" , "simple")
|
||||
|
|
|
@ -61,7 +61,7 @@ writeOrg opts document =
|
|||
pandocToOrg :: Pandoc -> State WriterState String
|
||||
pandocToOrg (Pandoc meta blocks) = do
|
||||
opts <- liftM stOptions get
|
||||
let colwidth = if writerWrapText opts
|
||||
let colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
metadata <- metaToJSON opts
|
||||
|
@ -275,6 +275,12 @@ inlineToOrg (RawInline f str) | f == "tex" || f == "latex" = return $ text str
|
|||
inlineToOrg (RawInline _ _) = return empty
|
||||
inlineToOrg (LineBreak) = return (text "\\\\" <> cr)
|
||||
inlineToOrg Space = return space
|
||||
inlineToOrg SoftBreak = do
|
||||
wrapText <- gets (writerWrapText . stOptions)
|
||||
case wrapText of
|
||||
WrapPreserve -> return cr
|
||||
WrapAuto -> return space
|
||||
WrapNone -> return space
|
||||
inlineToOrg (Link _ txt (src, _)) = do
|
||||
case txt of
|
||||
[Str x] | escapeURI x == src -> -- autolink
|
||||
|
|
|
@ -70,7 +70,7 @@ writeRST opts document =
|
|||
pandocToRST :: Pandoc -> State WriterState String
|
||||
pandocToRST (Pandoc meta blocks) = do
|
||||
opts <- liftM stOptions get
|
||||
let colwidth = if writerWrapText opts
|
||||
let colwidth = if writerWrapText opts == WrapAuto
|
||||
then Just $ writerColumns opts
|
||||
else Nothing
|
||||
let subtit = case lookupMeta "subtitle" meta of
|
||||
|
@ -378,11 +378,13 @@ inlineListToRST lst =
|
|||
surroundComplex _ _ = False
|
||||
okAfterComplex :: Inline -> Bool
|
||||
okAfterComplex Space = True
|
||||
okAfterComplex SoftBreak = True
|
||||
okAfterComplex LineBreak = True
|
||||
okAfterComplex (Str (c:_)) = isSpace c || c `elem` ("-.,:;!?\\/'\")]}>–—" :: String)
|
||||
okAfterComplex _ = False
|
||||
okBeforeComplex :: Inline -> Bool
|
||||
okBeforeComplex Space = True
|
||||
okBeforeComplex SoftBreak = True
|
||||
okBeforeComplex LineBreak = True
|
||||
okBeforeComplex (Str (c:_)) = isSpace c || c `elem` ("-:/'\"<([{–—" :: String)
|
||||
okBeforeComplex _ = False
|
||||
|
@ -446,6 +448,12 @@ inlineToRST (RawInline f x)
|
|||
| otherwise = return empty
|
||||
inlineToRST (LineBreak) = return cr -- there's no line break in RST (see Para)
|
||||
inlineToRST Space = return space
|
||||
inlineToRST SoftBreak = do
|
||||
wrapText <- gets (writerWrapText . stOptions)
|
||||
case wrapText of
|
||||
WrapPreserve -> return cr
|
||||
WrapAuto -> return space
|
||||
WrapNone -> return space
|
||||
-- autolink
|
||||
inlineToRST (Link _ [Str str] (src, _))
|
||||
| isURI src &&
|
||||
|
|
|
@ -349,6 +349,7 @@ inlineToRTF (RawInline f str)
|
|||
| f == Format "rtf" = str
|
||||
| otherwise = ""
|
||||
inlineToRTF (LineBreak) = "\\line "
|
||||
inlineToRTF SoftBreak = " "
|
||||
inlineToRTF Space = " "
|
||||
inlineToRTF (Link _ text (src, _)) =
|
||||
"{\\field{\\*\\fldinst{HYPERLINK \"" ++ (codeStringToRTF src) ++
|
||||
|
|
|
@ -75,7 +75,7 @@ pandocToTexinfo :: WriterOptions -> Pandoc -> State WriterState String
|
|||
pandocToTexinfo options (Pandoc meta blocks) = do
|
||||
let titlePage = not $ all null
|
||||
$ docTitle meta : docDate meta : docAuthors meta
|
||||
let colwidth = if writerWrapText options
|
||||
let colwidth = if writerWrapText options == WrapAuto
|
||||
then Just $ writerColumns options
|
||||
else Nothing
|
||||
metadata <- metaToJSON options
|
||||
|
@ -425,6 +425,12 @@ inlineToTexinfo (RawInline f str)
|
|||
| f == "texinfo" = return $ text str
|
||||
| otherwise = return empty
|
||||
inlineToTexinfo (LineBreak) = return $ text "@*" <> cr
|
||||
inlineToTexinfo SoftBreak = do
|
||||
wrapText <- gets (writerWrapText . stOptions)
|
||||
case wrapText of
|
||||
WrapAuto -> return space
|
||||
WrapNone -> return space
|
||||
WrapPreserve -> return cr
|
||||
inlineToTexinfo Space = return space
|
||||
|
||||
inlineToTexinfo (Link _ txt (src@('#':_), _)) = do
|
||||
|
|
|
@ -434,6 +434,8 @@ inlineToTextile opts (RawInline f str)
|
|||
|
||||
inlineToTextile _ (LineBreak) = return "\n"
|
||||
|
||||
inlineToTextile _ SoftBreak = return " "
|
||||
|
||||
inlineToTextile _ Space = return " "
|
||||
|
||||
inlineToTextile opts (Link (_, cls, _) txt (src, _)) = do
|
||||
|
|
|
@ -157,7 +157,7 @@ tests = [ testGroup "inline code"
|
|||
, "emph and strong emph alternating" =:
|
||||
"*xxx* ***xxx*** xxx\n*xxx* ***xxx*** xxx"
|
||||
=?> para (emph "xxx" <> space <> strong (emph "xxx") <>
|
||||
space <> "xxx" <> space <>
|
||||
space <> "xxx" <> softbreak <>
|
||||
emph "xxx" <> space <> strong (emph "xxx") <>
|
||||
space <> "xxx")
|
||||
, "emph with spaced strong" =:
|
||||
|
@ -325,7 +325,8 @@ tests = [ testGroup "inline code"
|
|||
]
|
||||
, "laziness" =:
|
||||
"foo1\n : bar\nbaz\n : bar2\n" =?>
|
||||
definitionList [ (text "foo1", [plain (text "bar baz"),
|
||||
definitionList [ (text "foo1", [plain (text "bar" <>
|
||||
softbreak <> text "baz"),
|
||||
plain (text "bar2")])
|
||||
]
|
||||
, "no blank space before first of two paragraphs" =:
|
||||
|
@ -347,7 +348,8 @@ tests = [ testGroup "inline code"
|
|||
, testGroup "+compact_definition_lists"
|
||||
[ test markdownCDL "basic compact list" $
|
||||
"foo1\n: bar\n baz\nfoo2\n: bar2\n" =?>
|
||||
definitionList [ (text "foo1", [plain (text "bar baz")])
|
||||
definitionList [ (text "foo1", [plain (text "bar" <> softbreak <>
|
||||
text "baz")])
|
||||
, (text "foo2", [plain (text "bar2")])
|
||||
]
|
||||
]
|
||||
|
|
|
@ -7,7 +7,7 @@ import Tests.Helpers
|
|||
import Tests.Arbitrary()
|
||||
|
||||
asciidoc :: (ToString a, ToPandoc a) => a -> String
|
||||
asciidoc = writeAsciiDoc def{ writerWrapText = False } . toPandoc
|
||||
asciidoc = writeAsciiDoc def{ writerWrapText = WrapNone } . toPandoc
|
||||
|
||||
tests :: [Test]
|
||||
tests = [ testGroup "emphasis"
|
||||
|
|
|
@ -11,7 +11,7 @@ context :: (ToString a, ToPandoc a) => a -> String
|
|||
context = writeConTeXt def . toPandoc
|
||||
|
||||
context' :: (ToString a, ToPandoc a) => a -> String
|
||||
context' = writeConTeXt def{ writerWrapText = False } . toPandoc
|
||||
context' = writeConTeXt def{ writerWrapText = WrapNone } . toPandoc
|
||||
|
||||
{-
|
||||
"my test" =: X =?> Y
|
||||
|
|
|
@ -8,7 +8,7 @@ import Tests.Helpers
|
|||
import Tests.Arbitrary()
|
||||
|
||||
docbook :: (ToString a, ToPandoc a) => a -> String
|
||||
docbook = writeDocbook def{ writerWrapText = False } . toPandoc
|
||||
docbook = writeDocbook def{ writerWrapText = WrapNone } . toPandoc
|
||||
|
||||
{-
|
||||
"my test" =: X =?> Y
|
||||
|
|
|
@ -8,7 +8,7 @@ import Tests.Helpers
|
|||
import Tests.Arbitrary()
|
||||
|
||||
html :: (ToString a, ToPandoc a) => a -> String
|
||||
html = writeHtmlString def{ writerWrapText = False } . toPandoc
|
||||
html = writeHtmlString def{ writerWrapText = WrapNone } . toPandoc
|
||||
|
||||
{-
|
||||
"my test" =: X =?> Y
|
||||
|
|
|
@ -1,7 +1,7 @@
|
|||
[Header 1 ("lhs-test",[],[]) [Str "lhs",Space,Str "test"]
|
||||
,Para [Code ("",[],[]) "unsplit",Space,Str "is",Space,Str "an",Space,Str "arrow",Space,Str "that",Space,Str "takes",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "and",Space,Str "combines",Space,Str "them",Space,Str "to",Space,Str "return",Space,Str "a",Space,Str "single",Space,Str "value:"]
|
||||
,Para [Code ("",[],[]) "unsplit",Space,Str "is",Space,Str "an",Space,Str "arrow",Space,Str "that",Space,Str "takes",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "and",Space,Str "combines",Space,Str "them",Space,Str "to",Space,Str "return",SoftBreak,Str "a",Space,Str "single",Space,Str "value:"]
|
||||
,CodeBlock ("",["sourceCode","literate","haskell"],[]) "unsplit :: (Arrow a) => (b -> c -> d) -> a (b, c) d\nunsplit = arr . uncurry\n -- arr (\\op (x,y) -> x `op` y)"
|
||||
,Para [Code ("",[],[]) "(***)",Space,Str "combines",Space,Str "two",Space,Str "arrows",Space,Str "into",Space,Str "a",Space,Str "new",Space,Str "arrow",Space,Str "by",Space,Str "running",Space,Str "the",Space,Str "two",Space,Str "arrows",Space,Str "on",Space,Str "a",Space,Str "pair",Space,Str "of",Space,Str "values",Space,Str "(one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "first",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair",Space,Str "and",Space,Str "one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "second",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair)."]
|
||||
,Para [Code ("",[],[]) "(***)",Space,Str "combines",Space,Str "two",Space,Str "arrows",Space,Str "into",Space,Str "a",Space,Str "new",Space,Str "arrow",Space,Str "by",Space,Str "running",Space,Str "the",Space,Str "two",Space,Str "arrows",Space,Str "on",Space,Str "a",SoftBreak,Str "pair",Space,Str "of",Space,Str "values",Space,Str "(one",Space,Str "arrow",Space,Str "on",Space,Str "the",Space,Str "first",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair",Space,Str "and",Space,Str "one",Space,Str "arrow",Space,Str "on",Space,Str "the",SoftBreak,Str "second",Space,Str "item",Space,Str "of",Space,Str "the",Space,Str "pair)."]
|
||||
,CodeBlock ("",[],[]) "f *** g = first f >>> second g"
|
||||
,Para [Str "Block",Space,Str "quote:"]
|
||||
,BlockQuote
|
||||
|
|
|
@ -1,4 +1,5 @@
|
|||
[Header 1 ("additional-markdown-reader-tests",[],[]) [Str "Additional",Space,Str "markdown",Space,Str "reader",Space,Str "tests"]
|
||||
[Para [Str "spanning",Space,Str "multiple",Space,Str "lines",SoftBreak,Str "%",Space,Str "Author",Space,Str "One",SoftBreak,Str "Author",Space,Str "Two;",Space,Str "Author",Space,Str "Three;",SoftBreak,Str "Author",Space,Str "Four"]
|
||||
,Header 1 ("additional-markdown-reader-tests",[],[]) [Str "Additional",Space,Str "markdown",Space,Str "reader",Space,Str "tests"]
|
||||
,Header 2 ("blank-line-before-url-in-link-reference",[],[]) [Str "Blank",Space,Str "line",Space,Str "before",Space,Str "URL",Space,Str "in",Space,Str "link",Space,Str "reference"]
|
||||
,Para [Link ("",[],[]) [Str "foo"] ("/url",""),Space,Str "and",Space,Link ("",[],[]) [Str "bar"] ("/url","title")]
|
||||
,Header 2 ("raw-context-environments",[],[]) [Str "Raw",Space,Str "ConTeXt",Space,Str "environments"]
|
||||
|
@ -6,7 +7,7 @@
|
|||
,RawBlock (Format "context") "\\startformula\n L_{1} = L_{2}\n \\stopformula"
|
||||
,RawBlock (Format "context") "\\start[a2]\n\\start[a2]\n\\stop[a2]\n\\stop[a2]"
|
||||
,Header 2 ("urls-with-spaces-and-punctuation",[],[]) [Str "URLs",Space,Str "with",Space,Str "spaces",Space,Str "and",Space,Str "punctuation"]
|
||||
,Para [Link ("",[],[]) [Str "foo"] ("/bar%20and%20baz",""),Space,Link ("",[],[]) [Str "foo"] ("/bar%20and%20baz",""),Space,Link ("",[],[]) [Str "foo"] ("/bar%20and%20baz",""),Space,Link ("",[],[]) [Str "foo"] ("bar%20baz","title")]
|
||||
,Para [Link ("",[],[]) [Str "foo"] ("/bar%20and%20baz",""),SoftBreak,Link ("",[],[]) [Str "foo"] ("/bar%20and%20baz",""),SoftBreak,Link ("",[],[]) [Str "foo"] ("/bar%20and%20baz",""),SoftBreak,Link ("",[],[]) [Str "foo"] ("bar%20baz","title")]
|
||||
,Para [Link ("",[],[]) [Str "baz"] ("/foo%20foo",""),Space,Link ("",[],[]) [Str "bam"] ("/foo%20fee",""),Space,Link ("",[],[]) [Str "bork"] ("/foo/zee%20zob","title")]
|
||||
,Para [Link ("",[],[]) [Str "Ward\8217s",Space,Str "method."] ("http://en.wikipedia.org/wiki/Ward's_method","")]
|
||||
,Header 2 ("horizontal-rules-with-spaces-at-end",[],[]) [Str "Horizontal",Space,Str "rules",Space,Str "with",Space,Str "spaces",Space,Str "at",Space,Str "end"]
|
||||
|
@ -22,7 +23,7 @@
|
|||
,Para [Str "$PATH",Space,Str "90",Space,Str "$PATH"]
|
||||
,Header 2 ("commented-out-list-item",[],[]) [Str "Commented-out",Space,Str "list",Space,Str "item"]
|
||||
,BulletList
|
||||
[[Plain [Str "one",Space,RawInline (Format "html") "<!--\n- two\n-->"]]
|
||||
[[Plain [Str "one",SoftBreak,RawInline (Format "html") "<!--\n- two\n-->"]]
|
||||
,[Plain [Str "three"]]]
|
||||
,Header 2 ("indented-code-at-beginning-of-list",[],[]) [Str "Indented",Space,Str "code",Space,Str "at",Space,Str "beginning",Space,Str "of",Space,Str "list"]
|
||||
,BulletList
|
||||
|
@ -90,9 +91,9 @@
|
|||
[[Plain [Str "col",Space,Str "1"]]
|
||||
,[Plain [Str "col",Space,Str "2"]]
|
||||
,[Plain [Str "col",Space,Str "3"]]]
|
||||
[[[Para [Str "r1",Space,Str "a",Space,Str "r1",Space,Str "bis"]]
|
||||
,[Para [Str "b",Space,Str "b",Space,Str "2"]]
|
||||
,[Para [Str "c",Space,Str "c",Space,Str "2"]]]
|
||||
[[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,[[Para [Str "r2",Space,Str "d"]]
|
||||
,[Para [Str "e"]]
|
||||
,[Para [Str "f"]]]]
|
||||
|
@ -101,9 +102,9 @@
|
|||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Para [Str "r1",Space,Str "a",Space,Str "r1",Space,Str "bis"]]
|
||||
,[Para [Str "b",Space,Str "b",Space,Str "2"]]
|
||||
,[Para [Str "c",Space,Str "c",Space,Str "2"]]]
|
||||
[[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,[[Para [Str "r2",Space,Str "d"]]
|
||||
,[Para [Str "e"]]
|
||||
,[Para [Str "f"]]]]
|
||||
|
@ -112,9 +113,9 @@
|
|||
[[]
|
||||
,[]
|
||||
,[]]
|
||||
[[[Para [Str "r1",Space,Str "a",Space,Str "r1",Space,Str "bis"]]
|
||||
,[Para [Str "b",Space,Str "b",Space,Str "2"]]
|
||||
,[Para [Str "c",Space,Str "c",Space,Str "2"]]]
|
||||
[[[Para [Str "r1",Space,Str "a",SoftBreak,Str "r1",Space,Str "bis"]]
|
||||
,[Para [Str "b",SoftBreak,Str "b",Space,Str "2"]]
|
||||
,[Para [Str "c",SoftBreak,Str "c",Space,Str "2"]]]
|
||||
,[[Para [Str "r2",Space,Str "d"]]
|
||||
,[Para [Str "e"]]
|
||||
,[Para [Str "f"]]]]
|
||||
|
@ -135,7 +136,7 @@
|
|||
[[Plain [Str "b"]]
|
||||
,[Plain [Str "b",Space,Str "2"]]
|
||||
,[Plain [Str "b",Space,Str "2"]]]]
|
||||
,[Para [Str "c",Space,Str "c",Space,Str "2",Space,Str "c",Space,Str "2"]]]]
|
||||
,[Para [Str "c",SoftBreak,Str "c",Space,Str "2",SoftBreak,Str "c",Space,Str "2"]]]]
|
||||
,Para [Str "Empty",Space,Str "cells"]
|
||||
,Table [] [AlignDefault,AlignDefault] [5.555555555555555e-2,5.555555555555555e-2]
|
||||
[[]
|
||||
|
@ -156,7 +157,7 @@
|
|||
,Header 2 ("reference-link-fallbacks",[],[]) [Str "Reference",Space,Str "link",Space,Str "fallbacks"]
|
||||
,Para [Str "[",Emph [Str "not",Space,Str "a",Space,Str "link"],Str "]",Space,Str "[",Emph [Str "nope"],Str "]\8230"]
|
||||
,Header 2 ("reference-link-followed-by-a-citation",[],[]) [Str "Reference",Space,Str "link",Space,Str "followed",Space,Str "by",Space,Str "a",Space,Str "citation"]
|
||||
,Para [Str "MapReduce",Space,Str "is",Space,Str "a",Space,Str "paradigm",Space,Str "popularized",Space,Str "by",Space,Link ("",[],[]) [Str "Google"] ("http://google.com",""),Space,Cite [Citation {citationId = "mapreduce", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@mapreduce]"],Space,Str "as",Space,Str "its",Space,Str "most",Space,Str "vocal",Space,Str "proponent."]
|
||||
,Para [Str "MapReduce",Space,Str "is",Space,Str "a",Space,Str "paradigm",Space,Str "popularized",Space,Str "by",Space,Link ("",[],[]) [Str "Google"] ("http://google.com",""),Space,Cite [Citation {citationId = "mapreduce", citationPrefix = [], citationSuffix = [], citationMode = NormalCitation, citationNoteNum = 0, citationHash = 0}] [Str "[@mapreduce]"],Space,Str "as",Space,Str "its",SoftBreak,Str "most",Space,Str "vocal",Space,Str "proponent."]
|
||||
,Header 2 ("empty-reference-links",[],[]) [Str "Empty",Space,Str "reference",Space,Str "links"]
|
||||
,Para [Str "bar"]
|
||||
,Para [Link ("",[],[]) [Str "foo2"] ("","")]
|
||||
|
|
|
@ -53,33 +53,33 @@
|
|||
,[Plain [Str "1"]]
|
||||
,[Plain [Str "1"]]]]
|
||||
,Para [Str "Multiline",Space,Str "table",Space,Str "with",Space,Str "caption:"]
|
||||
,Table [Str "Here's",Space,Str "the",Space,Str "caption.",Space,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375]
|
||||
[[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
,[Plain [Str "Right",Space,Str "Aligned"]]
|
||||
,Table [Str "Here's",Space,Str "the",Space,Str "caption.",SoftBreak,Str "It",Space,Str "may",Space,Str "span",Space,Str "multiple",Space,Str "lines."] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375]
|
||||
[[Plain [Str "Centered",SoftBreak,Str "Header"]]
|
||||
,[Plain [Str "Left",SoftBreak,Str "Aligned"]]
|
||||
,[Plain [Str "Right",SoftBreak,Str "Aligned"]]
|
||||
,[Plain [Str "Default",Space,Str "aligned"]]]
|
||||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12.0"]]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",SoftBreak,Str "multiple",Space,Str "lines."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5.0"]]
|
||||
,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
,Para [Str "Multiline",Space,Str "table",Space,Str "without",Space,Str "caption:"]
|
||||
,Table [] [AlignCenter,AlignLeft,AlignRight,AlignLeft] [0.15,0.1375,0.1625,0.3375]
|
||||
[[Plain [Str "Centered",Space,Str "Header"]]
|
||||
,[Plain [Str "Left",Space,Str "Aligned"]]
|
||||
,[Plain [Str "Right",Space,Str "Aligned"]]
|
||||
[[Plain [Str "Centered",SoftBreak,Str "Header"]]
|
||||
,[Plain [Str "Left",SoftBreak,Str "Aligned"]]
|
||||
,[Plain [Str "Right",SoftBreak,Str "Aligned"]]
|
||||
,[Plain [Str "Default",Space,Str "aligned"]]]
|
||||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12.0"]]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",SoftBreak,Str "multiple",Space,Str "lines."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5.0"]]
|
||||
,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]
|
||||
,Para [Str "Table",Space,Str "without",Space,Str "column",Space,Str "headers:"]
|
||||
,Table [] [AlignRight,AlignLeft,AlignCenter,AlignRight] [0.0,0.0,0.0,0.0]
|
||||
[[]
|
||||
|
@ -107,8 +107,8 @@
|
|||
[[[Plain [Str "First"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "12.0"]]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",Space,Str "multiple",Space,Str "lines."]]]
|
||||
,[Plain [Str "Example",Space,Str "of",Space,Str "a",Space,Str "row",Space,Str "that",Space,Str "spans",SoftBreak,Str "multiple",Space,Str "lines."]]]
|
||||
,[[Plain [Str "Second"]]
|
||||
,[Plain [Str "row"]]
|
||||
,[Plain [Str "5.0"]]
|
||||
,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",Space,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]]
|
||||
,[Plain [Str "Here's",Space,Str "another",Space,Str "one.",Space,Str "Note",SoftBreak,Str "the",Space,Str "blank",Space,Str "line",Space,Str "between",Space,Str "rows."]]]]]
|
||||
|
|
|
@ -1,5 +1,5 @@
|
|||
Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",SoftBreak,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("headers",[],[]) [Str "Headers"]
|
||||
,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link ("",[],[]) [Str "embedded",Space,Str "link"] ("/url","")]
|
||||
|
@ -15,14 +15,14 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,HorizontalRule
|
||||
,Header 1 ("paragraphs",[],[]) [Str "Paragraphs"]
|
||||
,Para [Str "Here\8217s",Space,Str "a",Space,Str "regular",Space,Str "paragraph."]
|
||||
,Para [Str "In",Space,Str "Markdown",Space,Str "1.0.0",Space,Str "and",Space,Str "earlier.",Space,Str "Version",Space,Str "8.",Space,Str "This",Space,Str "line",Space,Str "turns",Space,Str "into",Space,Str "a",Space,Str "list",Space,Str "item.",Space,Str "Because",Space,Str "a",Space,Str "hard-wrapped",Space,Str "line",Space,Str "in",Space,Str "the",Space,Str "middle",Space,Str "of",Space,Str "a",Space,Str "paragraph",Space,Str "looked",Space,Str "like",Space,Str "a",Space,Str "list",Space,Str "item."]
|
||||
,Para [Str "Here\8217s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet.",Space,Str "*",Space,Str "criminey."]
|
||||
,Para [Str "In",Space,Str "Markdown",Space,Str "1.0.0",Space,Str "and",Space,Str "earlier.",Space,Str "Version",SoftBreak,Str "8.",Space,Str "This",Space,Str "line",Space,Str "turns",Space,Str "into",Space,Str "a",Space,Str "list",Space,Str "item.",SoftBreak,Str "Because",Space,Str "a",Space,Str "hard-wrapped",Space,Str "line",Space,Str "in",Space,Str "the",SoftBreak,Str "middle",Space,Str "of",Space,Str "a",Space,Str "paragraph",Space,Str "looked",Space,Str "like",Space,Str "a",SoftBreak,Str "list",Space,Str "item."]
|
||||
,Para [Str "Here\8217s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet.",SoftBreak,Str "*",Space,Str "criminey."]
|
||||
,Para [Str "There",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "hard",Space,Str "line",Space,Str "break",LineBreak,Str "here."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("block-quotes",[],[]) [Str "Block",Space,Str "Quotes"]
|
||||
,Para [Str "E-mail",Space,Str "style:"]
|
||||
,BlockQuote
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote.",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short."]]
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote.",SoftBreak,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short."]]
|
||||
,BlockQuote
|
||||
[Para [Str "Code",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote:"]
|
||||
,CodeBlock ("",[],[]) "sub status {\n print \"working\";\n}"
|
||||
|
@ -35,7 +35,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
[Para [Str "nested"]]
|
||||
,BlockQuote
|
||||
[Para [Str "nested"]]]
|
||||
,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "block",Space,Str "quote:",Space,Str "2",Space,Str ">",Space,Str "1."]
|
||||
,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "block",Space,Str "quote:",Space,Str "2",SoftBreak,Str ">",Space,Str "1."]
|
||||
,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("code-blocks",[],[]) [Str "Code",Space,Str "Blocks"]
|
||||
|
@ -100,7 +100,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,Para [Str "Multiple",Space,Str "paragraphs:"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "Item",Space,Str "1,",Space,Str "graf",Space,Str "one."]
|
||||
,Para [Str "Item",Space,Str "1.",Space,Str "graf",Space,Str "two.",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog\8217s",Space,Str "back."]]
|
||||
,Para [Str "Item",Space,Str "1.",Space,Str "graf",Space,Str "two.",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog\8217s",SoftBreak,Str "back."]]
|
||||
,[Para [Str "Item",Space,Str "2."]]
|
||||
,[Para [Str "Item",Space,Str "3."]]]
|
||||
,Header 2 ("nested",[],[]) [Str "Nested"]
|
||||
|
@ -130,18 +130,18 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,[Para [Str "Third"]]]
|
||||
,Header 2 ("tabs-and-spaces",[],[]) [Str "Tabs",Space,Str "and",Space,Str "spaces"]
|
||||
,BulletList
|
||||
[[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "tabs"]]
|
||||
,[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "spaces"]
|
||||
[[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",SoftBreak,Str "indented",Space,Str "with",Space,Str "tabs"]]
|
||||
,[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",SoftBreak,Str "indented",Space,Str "with",Space,Str "spaces"]
|
||||
,BulletList
|
||||
[[Para [Str "this",Space,Str "is",Space,Str "an",Space,Str "example",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "tabs"]]
|
||||
,[Para [Str "this",Space,Str "is",Space,Str "an",Space,Str "example",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "spaces"]]]]]
|
||||
[[Para [Str "this",Space,Str "is",Space,Str "an",Space,Str "example",Space,Str "list",Space,Str "item",SoftBreak,Str "indented",Space,Str "with",Space,Str "tabs"]]
|
||||
,[Para [Str "this",Space,Str "is",Space,Str "an",Space,Str "example",Space,Str "list",Space,Str "item",SoftBreak,Str "indented",Space,Str "with",Space,Str "spaces"]]]]]
|
||||
,Header 2 ("fancy-list-markers",[],[]) [Str "Fancy",Space,Str "list",Space,Str "markers"]
|
||||
,OrderedList (2,Decimal,TwoParens)
|
||||
[[Plain [Str "begins",Space,Str "with",Space,Str "2"]]
|
||||
,[Para [Str "and",Space,Str "now",Space,Str "3"]
|
||||
,Para [Str "with",Space,Str "a",Space,Str "continuation"]
|
||||
,OrderedList (4,LowerRoman,Period)
|
||||
[[Plain [Str "sublist",Space,Str "with",Space,Str "roman",Space,Str "numerals,",Space,Str "starting",Space,Str "with",Space,Str "4"]]
|
||||
[[Plain [Str "sublist",Space,Str "with",Space,Str "roman",Space,Str "numerals,",SoftBreak,Str "starting",Space,Str "with",Space,Str "4"]]
|
||||
,[Plain [Str "more",Space,Str "items"]
|
||||
,OrderedList (1,UpperAlpha,TwoParens)
|
||||
[[Plain [Str "a",Space,Str "subsublist"]]
|
||||
|
@ -194,7 +194,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,DefinitionList
|
||||
[([Emph [Str "apple"]],
|
||||
[[Para [Str "red",Space,Str "fruit"]
|
||||
,Para [Str "contains",Space,Str "seeds,",Space,Str "crisp,",Space,Str "pleasant",Space,Str "to",Space,Str "taste"]]])
|
||||
,Para [Str "contains",Space,Str "seeds,",SoftBreak,Str "crisp,",Space,Str "pleasant",Space,Str "to",Space,Str "taste"]]])
|
||||
,([Emph [Str "orange"]],
|
||||
[[Para [Str "orange",Space,Str "fruit"]
|
||||
,CodeBlock ("",[],[]) "{ orange code block }"
|
||||
|
@ -260,7 +260,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,Div ("",[],[])
|
||||
[Div ("",[],[])
|
||||
[Div ("",[],[])
|
||||
[Plain [Str "foo"]]]]
|
||||
[Plain [Str "foo",SoftBreak]]]]
|
||||
,Para [Str "This",Space,Str "should",Space,Str "just",Space,Str "be",Space,Str "an",Space,Str "HTML",Space,Str "comment:"]
|
||||
,RawBlock (Format "html") "<!-- Comment -->"
|
||||
,Para [Str "Multiline:"]
|
||||
|
@ -295,13 +295,13 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,Para [Strikeout [Str "This",Space,Str "is",Space,Emph [Str "strikeout"],Str "."]]
|
||||
,Para [Str "Superscripts:",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Superscript [Emph [Str "hello"]],Space,Str "a",Superscript [Str "hello\160there"],Str "."]
|
||||
,Para [Str "Subscripts:",Space,Str "H",Subscript [Str "2"],Str "O,",Space,Str "H",Subscript [Str "23"],Str "O,",Space,Str "H",Subscript [Str "many\160of\160them"],Str "O."]
|
||||
,Para [Str "These",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "superscripts",Space,Str "or",Space,Str "subscripts,",Space,Str "because",Space,Str "of",Space,Str "the",Space,Str "unescaped",Space,Str "spaces:",Space,Str "a^b",Space,Str "c^d,",Space,Str "a~b",Space,Str "c~d."]
|
||||
,Para [Str "These",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "superscripts",Space,Str "or",Space,Str "subscripts,",SoftBreak,Str "because",Space,Str "of",Space,Str "the",Space,Str "unescaped",Space,Str "spaces:",Space,Str "a^b",Space,Str "c^d,",Space,Str "a~b",Space,Str "c~d."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("smart-quotes-ellipses-dashes",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"]
|
||||
,Para [Quoted DoubleQuote [Str "Hello,"],Space,Str "said",Space,Str "the",Space,Str "spider.",Space,Quoted DoubleQuote [Quoted SingleQuote [Str "Shelob"],Space,Str "is",Space,Str "my",Space,Str "name."]]
|
||||
,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters."]
|
||||
,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]]
|
||||
,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70\8217s?"]
|
||||
,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",SoftBreak,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]]
|
||||
,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",SoftBreak,Str "70\8217s?"]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link ("",[],[]) [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."]
|
||||
,Para [Str "Some",Space,Str "dashes:",Space,Str "one\8212two",Space,Str "\8212",Space,Str "three\8212four",Space,Str "\8212",Space,Str "five."]
|
||||
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5\8211\&7,",Space,Str "255\8211\&66,",Space,Str "1987\8211\&1999."]
|
||||
|
@ -315,12 +315,12 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,[Plain [Math InlineMath "\\alpha \\wedge \\omega"]]
|
||||
,[Plain [Math InlineMath "223"]]
|
||||
,[Plain [Math InlineMath "p",Str "-Tree"]]
|
||||
,[Plain [Str "Here\8217s",Space,Str "some",Space,Str "display",Space,Str "math:",Space,Math DisplayMath "\\frac{d}{dx}f(x)=\\lim_{h\\to 0}\\frac{f(x+h)-f(x)}{h}"]]
|
||||
,[Plain [Str "Here\8217s",Space,Str "some",Space,Str "display",Space,Str "math:",SoftBreak,Math DisplayMath "\\frac{d}{dx}f(x)=\\lim_{h\\to 0}\\frac{f(x+h)-f(x)}{h}"]]
|
||||
,[Plain [Str "Here\8217s",Space,Str "one",Space,Str "that",Space,Str "has",Space,Str "a",Space,Str "line",Space,Str "break",Space,Str "in",Space,Str "it:",Space,Math InlineMath "\\alpha + \\omega \\times x^2",Str "."]]]
|
||||
,Para [Str "These",Space,Str "shouldn\8217t",Space,Str "be",Space,Str "math:"]
|
||||
,BulletList
|
||||
[[Plain [Str "To",Space,Str "get",Space,Str "the",Space,Str "famous",Space,Str "equation,",Space,Str "write",Space,Code ("",[],[]) "$e = mc^2$",Str "."]]
|
||||
,[Plain [Str "$22,000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money.",Space,Str "So",Space,Str "is",Space,Str "$34,000.",Space,Str "(It",Space,Str "worked",Space,Str "if",Space,Quoted DoubleQuote [Str "lot"],Space,Str "is",Space,Str "emphasized.)"]]
|
||||
,[Plain [Str "$22,000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money.",Space,Str "So",Space,Str "is",Space,Str "$34,000.",SoftBreak,Str "(It",Space,Str "worked",Space,Str "if",Space,Quoted DoubleQuote [Str "lot"],Space,Str "is",Space,Str "emphasized.)"]]
|
||||
,[Plain [Str "Shoes",Space,Str "($20)",Space,Str "and",Space,Str "socks",Space,Str "($5)."]]
|
||||
,[Plain [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23$."]]]
|
||||
,Para [Str "Here\8217s",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
|
||||
|
@ -403,7 +403,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [Str "movie"] ("movie.jpg",""),Space,Str "icon."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("footnotes",[],[]) [Str "Footnotes"]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link ("",[],[]) [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",SoftBreak,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",SoftBreak,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",SoftBreak,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",SoftBreak,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],SoftBreak,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",SoftBreak,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",SoftBreak,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",SoftBreak,Link ("",[],[]) [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",SoftBreak,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]]
|
||||
,BlockQuote
|
||||
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
|
|
|
@ -912,7 +912,7 @@ These should not be escaped: \$ \\ \> \[ \{
|
|||
Now, nested:
|
||||
</para>
|
||||
<para>
|
||||
foo
|
||||
foo
|
||||
</para>
|
||||
<para>
|
||||
This should just be an HTML comment:
|
||||
|
|
|
@ -350,7 +350,7 @@ As should this:
|
|||
</code>
|
||||
Now, nested:
|
||||
|
||||
foo
|
||||
foo
|
||||
|
||||
|
||||
|
||||
|
|
File diff suppressed because one or more lines are too long
|
@ -362,7 +362,7 @@ And this is <strong>strong</strong>
|
|||
<div>
|
||||
<div>
|
||||
<div>
|
||||
foo
|
||||
foo
|
||||
</div>
|
||||
</div>
|
||||
</div>
|
||||
|
|
|
@ -1439,7 +1439,7 @@ These should not be escaped: \$ \\ \> \[ \{</Content>
|
|||
</ParagraphStyleRange>
|
||||
<ParagraphStyleRange AppliedParagraphStyle="">
|
||||
<CharacterStyleRange AppliedCharacterStyle="$ID/NormalCharacterStyle">
|
||||
<Content>foo</Content>
|
||||
<Content>foo </Content>
|
||||
</CharacterStyleRange><Br />
|
||||
</ParagraphStyleRange>
|
||||
<ParagraphStyleRange AppliedParagraphStyle="ParagraphStyle/Paragraph">
|
||||
|
|
|
@ -374,7 +374,7 @@ Now, nested:
|
|||
|
||||
<div>
|
||||
|
||||
foo
|
||||
foo
|
||||
|
||||
</div>
|
||||
|
||||
|
|
|
@ -1,5 +1,5 @@
|
|||
Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Space,Str "MacFarlane"],MetaInlines [Str "Anonymous"]]),("date",MetaInlines [Str "July",Space,Str "17,",Space,Str "2006"]),("title",MetaInlines [Str "Pandoc",Space,Str "Test",Space,Str "Suite"])]})
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",Space,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "set",Space,Str "of",Space,Str "tests",Space,Str "for",Space,Str "pandoc.",Space,Str "Most",Space,Str "of",Space,Str "them",Space,Str "are",Space,Str "adapted",Space,Str "from",SoftBreak,Str "John",Space,Str "Gruber\8217s",Space,Str "markdown",Space,Str "test",Space,Str "suite."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("headers",[],[]) [Str "Headers"]
|
||||
,Header 2 ("level-2-with-an-embedded-link",[],[]) [Str "Level",Space,Str "2",Space,Str "with",Space,Str "an",Space,Link ("",[],[]) [Str "embedded",Space,Str "link"] ("/url","")]
|
||||
|
@ -15,14 +15,14 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,HorizontalRule
|
||||
,Header 1 ("paragraphs",[],[]) [Str "Paragraphs"]
|
||||
,Para [Str "Here\8217s",Space,Str "a",Space,Str "regular",Space,Str "paragraph."]
|
||||
,Para [Str "In",Space,Str "Markdown",Space,Str "1.0.0",Space,Str "and",Space,Str "earlier.",Space,Str "Version",Space,Str "8.",Space,Str "This",Space,Str "line",Space,Str "turns",Space,Str "into",Space,Str "a",Space,Str "list",Space,Str "item.",Space,Str "Because",Space,Str "a",Space,Str "hard-wrapped",Space,Str "line",Space,Str "in",Space,Str "the",Space,Str "middle",Space,Str "of",Space,Str "a",Space,Str "paragraph",Space,Str "looked",Space,Str "like",Space,Str "a",Space,Str "list",Space,Str "item."]
|
||||
,Para [Str "Here\8217s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet.",Space,Str "*",Space,Str "criminey."]
|
||||
,Para [Str "In",Space,Str "Markdown",Space,Str "1.0.0",Space,Str "and",Space,Str "earlier.",Space,Str "Version",SoftBreak,Str "8.",Space,Str "This",Space,Str "line",Space,Str "turns",Space,Str "into",Space,Str "a",Space,Str "list",Space,Str "item.",SoftBreak,Str "Because",Space,Str "a",Space,Str "hard-wrapped",Space,Str "line",Space,Str "in",Space,Str "the",SoftBreak,Str "middle",Space,Str "of",Space,Str "a",Space,Str "paragraph",Space,Str "looked",Space,Str "like",Space,Str "a",SoftBreak,Str "list",Space,Str "item."]
|
||||
,Para [Str "Here\8217s",Space,Str "one",Space,Str "with",Space,Str "a",Space,Str "bullet.",SoftBreak,Str "*",Space,Str "criminey."]
|
||||
,Para [Str "There",Space,Str "should",Space,Str "be",Space,Str "a",Space,Str "hard",Space,Str "line",Space,Str "break",LineBreak,Str "here."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("block-quotes",[],[]) [Str "Block",Space,Str "Quotes"]
|
||||
,Para [Str "E-mail",Space,Str "style:"]
|
||||
,BlockQuote
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote.",Space,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short."]]
|
||||
[Para [Str "This",Space,Str "is",Space,Str "a",Space,Str "block",Space,Str "quote.",SoftBreak,Str "It",Space,Str "is",Space,Str "pretty",Space,Str "short."]]
|
||||
,BlockQuote
|
||||
[Para [Str "Code",Space,Str "in",Space,Str "a",Space,Str "block",Space,Str "quote:"]
|
||||
,CodeBlock ("",[],[]) "sub status {\n print \"working\";\n}"
|
||||
|
@ -35,7 +35,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
[Para [Str "nested"]]
|
||||
,BlockQuote
|
||||
[Para [Str "nested"]]]
|
||||
,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "block",Space,Str "quote:",Space,Str "2",Space,Str ">",Space,Str "1."]
|
||||
,Para [Str "This",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "a",Space,Str "block",Space,Str "quote:",Space,Str "2",SoftBreak,Str ">",Space,Str "1."]
|
||||
,Para [Str "And",Space,Str "a",Space,Str "following",Space,Str "paragraph."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("code-blocks",[],[]) [Str "Code",Space,Str "Blocks"]
|
||||
|
@ -100,7 +100,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,Para [Str "Multiple",Space,Str "paragraphs:"]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
[[Para [Str "Item",Space,Str "1,",Space,Str "graf",Space,Str "one."]
|
||||
,Para [Str "Item",Space,Str "1.",Space,Str "graf",Space,Str "two.",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog\8217s",Space,Str "back."]]
|
||||
,Para [Str "Item",Space,Str "1.",Space,Str "graf",Space,Str "two.",Space,Str "The",Space,Str "quick",Space,Str "brown",Space,Str "fox",Space,Str "jumped",Space,Str "over",Space,Str "the",Space,Str "lazy",Space,Str "dog\8217s",SoftBreak,Str "back."]]
|
||||
,[Para [Str "Item",Space,Str "2."]]
|
||||
,[Para [Str "Item",Space,Str "3."]]]
|
||||
,Header 2 ("nested",[],[]) [Str "Nested"]
|
||||
|
@ -130,18 +130,18 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,[Para [Str "Third"]]]
|
||||
,Header 2 ("tabs-and-spaces",[],[]) [Str "Tabs",Space,Str "and",Space,Str "spaces"]
|
||||
,BulletList
|
||||
[[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "tabs"]]
|
||||
,[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "spaces"]
|
||||
[[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",SoftBreak,Str "indented",Space,Str "with",Space,Str "tabs"]]
|
||||
,[Para [Str "this",Space,Str "is",Space,Str "a",Space,Str "list",Space,Str "item",SoftBreak,Str "indented",Space,Str "with",Space,Str "spaces"]
|
||||
,BulletList
|
||||
[[Para [Str "this",Space,Str "is",Space,Str "an",Space,Str "example",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "tabs"]]
|
||||
,[Para [Str "this",Space,Str "is",Space,Str "an",Space,Str "example",Space,Str "list",Space,Str "item",Space,Str "indented",Space,Str "with",Space,Str "spaces"]]]]]
|
||||
[[Para [Str "this",Space,Str "is",Space,Str "an",Space,Str "example",Space,Str "list",Space,Str "item",SoftBreak,Str "indented",Space,Str "with",Space,Str "tabs"]]
|
||||
,[Para [Str "this",Space,Str "is",Space,Str "an",Space,Str "example",Space,Str "list",Space,Str "item",SoftBreak,Str "indented",Space,Str "with",Space,Str "spaces"]]]]]
|
||||
,Header 2 ("fancy-list-markers",[],[]) [Str "Fancy",Space,Str "list",Space,Str "markers"]
|
||||
,OrderedList (2,Decimal,TwoParens)
|
||||
[[Plain [Str "begins",Space,Str "with",Space,Str "2"]]
|
||||
,[Para [Str "and",Space,Str "now",Space,Str "3"]
|
||||
,Para [Str "with",Space,Str "a",Space,Str "continuation"]
|
||||
,OrderedList (4,LowerRoman,Period)
|
||||
[[Plain [Str "sublist",Space,Str "with",Space,Str "roman",Space,Str "numerals,",Space,Str "starting",Space,Str "with",Space,Str "4"]]
|
||||
[[Plain [Str "sublist",Space,Str "with",Space,Str "roman",Space,Str "numerals,",SoftBreak,Str "starting",Space,Str "with",Space,Str "4"]]
|
||||
,[Plain [Str "more",Space,Str "items"]
|
||||
,OrderedList (1,UpperAlpha,TwoParens)
|
||||
[[Plain [Str "a",Space,Str "subsublist"]]
|
||||
|
@ -194,7 +194,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,DefinitionList
|
||||
[([Emph [Str "apple"]],
|
||||
[[Para [Str "red",Space,Str "fruit"]
|
||||
,Para [Str "contains",Space,Str "seeds,",Space,Str "crisp,",Space,Str "pleasant",Space,Str "to",Space,Str "taste"]]])
|
||||
,Para [Str "contains",Space,Str "seeds,",SoftBreak,Str "crisp,",Space,Str "pleasant",Space,Str "to",Space,Str "taste"]]])
|
||||
,([Emph [Str "orange"]],
|
||||
[[Para [Str "orange",Space,Str "fruit"]
|
||||
,CodeBlock ("",[],[]) "{ orange code block }"
|
||||
|
@ -260,7 +260,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,Div ("",[],[])
|
||||
[Div ("",[],[])
|
||||
[Div ("",[],[])
|
||||
[Plain [Str "foo"]]]]
|
||||
[Plain [Str "foo",SoftBreak]]]]
|
||||
,Para [Str "This",Space,Str "should",Space,Str "just",Space,Str "be",Space,Str "an",Space,Str "HTML",Space,Str "comment:"]
|
||||
,RawBlock (Format "html") "<!-- Comment -->"
|
||||
,Para [Str "Multiline:"]
|
||||
|
@ -295,13 +295,13 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,Para [Strikeout [Str "This",Space,Str "is",Space,Emph [Str "strikeout"],Str "."]]
|
||||
,Para [Str "Superscripts:",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Superscript [Emph [Str "hello"]],Space,Str "a",Superscript [Str "hello\160there"],Str "."]
|
||||
,Para [Str "Subscripts:",Space,Str "H",Subscript [Str "2"],Str "O,",Space,Str "H",Subscript [Str "23"],Str "O,",Space,Str "H",Subscript [Str "many\160of\160them"],Str "O."]
|
||||
,Para [Str "These",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "superscripts",Space,Str "or",Space,Str "subscripts,",Space,Str "because",Space,Str "of",Space,Str "the",Space,Str "unescaped",Space,Str "spaces:",Space,Str "a^b",Space,Str "c^d,",Space,Str "a~b",Space,Str "c~d."]
|
||||
,Para [Str "These",Space,Str "should",Space,Str "not",Space,Str "be",Space,Str "superscripts",Space,Str "or",Space,Str "subscripts,",SoftBreak,Str "because",Space,Str "of",Space,Str "the",Space,Str "unescaped",Space,Str "spaces:",Space,Str "a^b",Space,Str "c^d,",Space,Str "a~b",Space,Str "c~d."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("smart-quotes-ellipses-dashes",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"]
|
||||
,Para [Quoted DoubleQuote [Str "Hello,"],Space,Str "said",Space,Str "the",Space,Str "spider.",Space,Quoted DoubleQuote [Quoted SingleQuote [Str "Shelob"],Space,Str "is",Space,Str "my",Space,Str "name."]]
|
||||
,Para [Quoted SingleQuote [Str "A"],Str ",",Space,Quoted SingleQuote [Str "B"],Str ",",Space,Str "and",Space,Quoted SingleQuote [Str "C"],Space,Str "are",Space,Str "letters."]
|
||||
,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",Space,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]]
|
||||
,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",Space,Str "70\8217s?"]
|
||||
,Para [Quoted SingleQuote [Str "Oak,"],Space,Quoted SingleQuote [Str "elm,"],Space,Str "and",Space,Quoted SingleQuote [Str "beech"],Space,Str "are",Space,Str "names",Space,Str "of",Space,Str "trees.",SoftBreak,Str "So",Space,Str "is",Space,Quoted SingleQuote [Str "pine."]]
|
||||
,Para [Quoted SingleQuote [Str "He",Space,Str "said,",Space,Quoted DoubleQuote [Str "I",Space,Str "want",Space,Str "to",Space,Str "go."]],Space,Str "Were",Space,Str "you",Space,Str "alive",Space,Str "in",Space,Str "the",SoftBreak,Str "70\8217s?"]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "some",Space,Str "quoted",Space,Quoted SingleQuote [Code ("",[],[]) "code"],Space,Str "and",Space,Str "a",Space,Quoted DoubleQuote [Link ("",[],[]) [Str "quoted",Space,Str "link"] ("http://example.com/?foo=1&bar=2","")],Str "."]
|
||||
,Para [Str "Some",Space,Str "dashes:",Space,Str "one\8212two",Space,Str "\8212",Space,Str "three\8212four",Space,Str "\8212",Space,Str "five."]
|
||||
,Para [Str "Dashes",Space,Str "between",Space,Str "numbers:",Space,Str "5\8211\&7,",Space,Str "255\8211\&66,",Space,Str "1987\8211\&1999."]
|
||||
|
@ -315,12 +315,12 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,[Plain [Math InlineMath "\\alpha \\wedge \\omega"]]
|
||||
,[Plain [Math InlineMath "223"]]
|
||||
,[Plain [Math InlineMath "p",Str "-Tree"]]
|
||||
,[Plain [Str "Here\8217s",Space,Str "some",Space,Str "display",Space,Str "math:",Space,Math DisplayMath "\\frac{d}{dx}f(x)=\\lim_{h\\to 0}\\frac{f(x+h)-f(x)}{h}"]]
|
||||
,[Plain [Str "Here\8217s",Space,Str "some",Space,Str "display",Space,Str "math:",SoftBreak,Math DisplayMath "\\frac{d}{dx}f(x)=\\lim_{h\\to 0}\\frac{f(x+h)-f(x)}{h}"]]
|
||||
,[Plain [Str "Here\8217s",Space,Str "one",Space,Str "that",Space,Str "has",Space,Str "a",Space,Str "line",Space,Str "break",Space,Str "in",Space,Str "it:",Space,Math InlineMath "\\alpha + \\omega \\times x^2",Str "."]]]
|
||||
,Para [Str "These",Space,Str "shouldn\8217t",Space,Str "be",Space,Str "math:"]
|
||||
,BulletList
|
||||
[[Plain [Str "To",Space,Str "get",Space,Str "the",Space,Str "famous",Space,Str "equation,",Space,Str "write",Space,Code ("",[],[]) "$e = mc^2$",Str "."]]
|
||||
,[Plain [Str "$22,000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money.",Space,Str "So",Space,Str "is",Space,Str "$34,000.",Space,Str "(It",Space,Str "worked",Space,Str "if",Space,Quoted DoubleQuote [Str "lot"],Space,Str "is",Space,Str "emphasized.)"]]
|
||||
,[Plain [Str "$22,000",Space,Str "is",Space,Str "a",Space,Emph [Str "lot"],Space,Str "of",Space,Str "money.",Space,Str "So",Space,Str "is",Space,Str "$34,000.",SoftBreak,Str "(It",Space,Str "worked",Space,Str "if",Space,Quoted DoubleQuote [Str "lot"],Space,Str "is",Space,Str "emphasized.)"]]
|
||||
,[Plain [Str "Shoes",Space,Str "($20)",Space,Str "and",Space,Str "socks",Space,Str "($5)."]]
|
||||
,[Plain [Str "Escaped",Space,Code ("",[],[]) "$",Str ":",Space,Str "$73",Space,Emph [Str "this",Space,Str "should",Space,Str "be",Space,Str "emphasized"],Space,Str "23$."]]]
|
||||
,Para [Str "Here\8217s",Space,Str "a",Space,Str "LaTeX",Space,Str "table:"]
|
||||
|
@ -403,7 +403,7 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "John",Spa
|
|||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "movie",Space,Image ("",[],[]) [Str "movie"] ("movie.jpg",""),Space,Str "icon."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("footnotes",[],[]) [Str "Footnotes"]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",Space,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",Space,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",Space,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",Space,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],Space,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",Space,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",Space,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",Space,Link ("",[],[]) [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]]
|
||||
,Para [Str "Here",Space,Str "is",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Note [Para [Str "Here",Space,Str "is",Space,Str "the",Space,Str "footnote.",Space,Str "It",Space,Str "can",Space,Str "go",Space,Str "anywhere",Space,Str "after",Space,Str "the",Space,Str "footnote",SoftBreak,Str "reference.",Space,Str "It",Space,Str "need",Space,Str "not",Space,Str "be",Space,Str "placed",Space,Str "at",Space,Str "the",Space,Str "end",Space,Str "of",Space,Str "the",Space,Str "document."]],Space,Str "and",Space,Str "another.",Note [Para [Str "Here\8217s",Space,Str "the",Space,Str "long",Space,Str "note.",Space,Str "This",Space,Str "one",Space,Str "contains",Space,Str "multiple",SoftBreak,Str "blocks."],Para [Str "Subsequent",Space,Str "blocks",Space,Str "are",Space,Str "indented",Space,Str "to",Space,Str "show",Space,Str "that",Space,Str "they",Space,Str "belong",Space,Str "to",Space,Str "the",SoftBreak,Str "footnote",Space,Str "(as",Space,Str "with",Space,Str "list",Space,Str "items)."],CodeBlock ("",[],[]) " { <code> }",Para [Str "If",Space,Str "you",Space,Str "want,",Space,Str "you",Space,Str "can",Space,Str "indent",Space,Str "every",Space,Str "line,",Space,Str "but",Space,Str "you",Space,Str "can",Space,Str "also",Space,Str "be",SoftBreak,Str "lazy",Space,Str "and",Space,Str "just",Space,Str "indent",Space,Str "the",Space,Str "first",Space,Str "line",Space,Str "of",Space,Str "each",Space,Str "block."]],SoftBreak,Str "This",Space,Str "should",Space,Emph [Str "not"],Space,Str "be",Space,Str "a",Space,Str "footnote",Space,Str "reference,",Space,Str "because",Space,Str "it",SoftBreak,Str "contains",Space,Str "a",Space,Str "space.[^my",Space,Str "note]",Space,Str "Here",Space,Str "is",Space,Str "an",Space,Str "inline",Space,Str "note.",Note [Para [Str "This",SoftBreak,Str "is",Space,Emph [Str "easier"],Space,Str "to",Space,Str "type.",Space,Str "Inline",Space,Str "notes",Space,Str "may",Space,Str "contain",SoftBreak,Link ("",[],[]) [Str "links"] ("http://google.com",""),Space,Str "and",Space,Code ("",[],[]) "]",Space,Str "verbatim",Space,Str "characters,",SoftBreak,Str "as",Space,Str "well",Space,Str "as",Space,Str "[bracketed",Space,Str "text]."]]]
|
||||
,BlockQuote
|
||||
[Para [Str "Notes",Space,Str "can",Space,Str "go",Space,Str "in",Space,Str "quotes.",Note [Para [Str "In",Space,Str "quote."]]]]
|
||||
,OrderedList (1,Decimal,Period)
|
||||
|
|
|
@ -1318,7 +1318,7 @@ though:</text:p>
|
|||
<text:p text:style-name="First_20_paragraph">As should this:</text:p>
|
||||
<text:p text:style-name="P48"><div>foo</div></text:p>
|
||||
<text:p text:style-name="First_20_paragraph">Now, nested:</text:p>
|
||||
<text:p text:style-name="Text_20_body">foo</text:p>
|
||||
<text:p text:style-name="Text_20_body">foo </text:p>
|
||||
<text:p text:style-name="Text_20_body">This should just be an HTML
|
||||
comment:</text:p>
|
||||
<text:p text:style-name="Text_20_body">Multiline:</text:p>
|
||||
|
|
|
@ -222,7 +222,7 @@ These should not be escaped: \\$ \\\\ \\> \\[ \\\{\par}
|
|||
{\pard \ql \f0 \sa180 \li0 \fi0 As should this:\par}
|
||||
{\pard \ql \f0 \sa180 \li0 \fi0 \f1 <div>foo</div>\par}
|
||||
{\pard \ql \f0 \sa180 \li0 \fi0 Now, nested:\par}
|
||||
{\pard \ql \f0 \sa0 \li0 \fi0 foo\par}
|
||||
{\pard \ql \f0 \sa0 \li0 \fi0 foo \par}
|
||||
{\pard \ql \f0 \sa180 \li0 \fi0 This should just be an HTML comment:\par}
|
||||
{\pard \ql \f0 \sa180 \li0 \fi0 Multiline:\par}
|
||||
{\pard \ql \f0 \sa180 \li0 \fi0 Code block:\par}
|
||||
|
|
|
@ -424,7 +424,7 @@ Now, nested:
|
|||
|
||||
<div>
|
||||
|
||||
foo
|
||||
foo
|
||||
|
||||
</div>
|
||||
|
||||
|
|
Loading…
Add table
Reference in a new issue