Support new Underline element in readers and writers (#6277)
Deprecate `underlineSpan` in Shared in favor of `Text.Pandoc.Builder.underline`.
This commit is contained in:
parent
8d09a92d97
commit
9c2b659eeb
53 changed files with 169 additions and 45 deletions
|
@ -829,13 +829,23 @@ M.Subscript = M.Inline:create_constructor(
|
|||
--- Creates a Superscript inline element
|
||||
-- @function Superscript
|
||||
-- @tparam {Inline,..} content inline content
|
||||
-- @treturn Inline strong element
|
||||
-- @treturn Inline superscript element
|
||||
M.Superscript = M.Inline:create_constructor(
|
||||
"Superscript",
|
||||
function(content) return {c = ensureInlineList(content)} end,
|
||||
"content"
|
||||
)
|
||||
|
||||
--- Creates an Underline inline element
|
||||
-- @function Underline
|
||||
-- @tparam {Inline,..} content inline content
|
||||
-- @treturn Inline underline element
|
||||
M.Underline = M.Inline:create_constructor(
|
||||
"Underline",
|
||||
function(content) return {c = ensureInlineList(content)} end,
|
||||
"content"
|
||||
)
|
||||
|
||||
|
||||
------------------------------------------------------------------------
|
||||
-- Element components
|
||||
|
|
|
@ -303,6 +303,7 @@ pushInline = \case
|
|||
Cite citations lst -> pushViaConstructor "Cite" lst citations
|
||||
Code attr lst -> pushViaConstructor "Code" lst (LuaAttr attr)
|
||||
Emph inlns -> pushViaConstructor "Emph" inlns
|
||||
Underline inlns -> pushViaConstructor "Underline" inlns
|
||||
Image attr alt (src,tit) -> pushViaConstructor "Image" alt src tit (LuaAttr attr)
|
||||
LineBreak -> pushViaConstructor "LineBreak"
|
||||
Link attr lst (src,tit) -> pushViaConstructor "Link" lst src tit (LuaAttr attr)
|
||||
|
@ -328,6 +329,7 @@ peekInline idx = defineHowTo "get Inline value" $ do
|
|||
"Cite" -> uncurry Cite <$> elementContent
|
||||
"Code" -> withAttr Code <$> elementContent
|
||||
"Emph" -> Emph <$> elementContent
|
||||
"Underline" -> Underline <$> elementContent
|
||||
"Image" -> (\(LuaAttr attr, lst, tgt) -> Image attr lst tgt)
|
||||
<$> elementContent
|
||||
"Link" -> (\(LuaAttr attr, lst, tgt) -> Link attr lst tgt)
|
||||
|
|
|
@ -299,7 +299,7 @@ runStyleToTransform rPr
|
|||
return $ subscript . transform
|
||||
| Just "single" <- rUnderline rPr = do
|
||||
transform <- runStyleToTransform rPr{rUnderline = Nothing}
|
||||
return $ underlineSpan . transform
|
||||
return $ Pandoc.underline . transform
|
||||
| otherwise = return id
|
||||
|
||||
runToInlines :: PandocMonad m => Run -> DocxContext m Inlines
|
||||
|
|
|
@ -29,7 +29,7 @@ import Text.Pandoc.Definition
|
|||
import Text.Pandoc.Error (PandocError (PandocParsecError))
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Parsing hiding (enclosed, nested)
|
||||
import Text.Pandoc.Shared (crFilter, trim, underlineSpan, stringify, tshow)
|
||||
import Text.Pandoc.Shared (crFilter, trim, stringify, tshow)
|
||||
|
||||
-- | Read DokuWiki from an input string and return a Pandoc document.
|
||||
readDokuWiki :: PandocMonad m
|
||||
|
@ -162,7 +162,7 @@ italic :: PandocMonad m => DWParser m B.Inlines
|
|||
italic = try $ B.emph <$> enclosed (string "//") nestedInlines
|
||||
|
||||
underlined :: PandocMonad m => DWParser m B.Inlines
|
||||
underlined = try $ underlineSpan <$> enclosed (string "__") nestedInlines
|
||||
underlined = try $ B.underline <$> enclosed (string "__") nestedInlines
|
||||
|
||||
nowiki :: PandocMonad m => DWParser m B.Inlines
|
||||
nowiki = try $ B.text <$ string "<nowiki>" <*> manyTillChar anyChar (try $ string "</nowiki>")
|
||||
|
|
|
@ -61,7 +61,7 @@ import Text.Pandoc.Options (
|
|||
import Text.Pandoc.Parsing hiding ((<|>))
|
||||
import Text.Pandoc.Shared (addMetaField, blocksToInlines', crFilter, escapeURI,
|
||||
extractSpaces, htmlSpanLikeElements, elemText, splitTextBy,
|
||||
onlySimpleTableCells, safeRead, underlineSpan, tshow)
|
||||
onlySimpleTableCells, safeRead, tshow)
|
||||
import Text.Pandoc.Walk
|
||||
import Text.Parsec.Error
|
||||
import Text.TeXMath (readMathML, writeTeX)
|
||||
|
@ -749,7 +749,7 @@ pStrikeout =
|
|||
return $ B.strikeout contents)
|
||||
|
||||
pUnderline :: PandocMonad m => TagParser m Inlines
|
||||
pUnderline = pInlinesInTags "u" underlineSpan <|> pInlinesInTags "ins" underlineSpan
|
||||
pUnderline = pInlinesInTags "u" B.underline <|> pInlinesInTags "ins" B.underline
|
||||
|
||||
pLineBreak :: PandocMonad m => TagParser m Inlines
|
||||
pLineBreak = do
|
||||
|
|
|
@ -26,7 +26,7 @@ import Text.HTML.TagSoup.Entity (lookupEntity)
|
|||
import Text.Pandoc.Builder
|
||||
import Text.Pandoc.Class.PandocMonad (PandocMonad)
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Shared (underlineSpan, crFilter, safeRead)
|
||||
import Text.Pandoc.Shared (crFilter, safeRead)
|
||||
import Text.TeXMath (readMathML, writeTeX)
|
||||
import Text.XML.Light
|
||||
import qualified Data.Set as S (fromList, member)
|
||||
|
@ -456,7 +456,7 @@ parseInline (Elem e) =
|
|||
"strike" -> strikeout <$> innerInlines
|
||||
"sub" -> subscript <$> innerInlines
|
||||
"sup" -> superscript <$> innerInlines
|
||||
"underline" -> underlineSpan <$> innerInlines
|
||||
"underline" -> underline <$> innerInlines
|
||||
"break" -> return linebreak
|
||||
"sc" -> smallcaps <$> innerInlines
|
||||
|
||||
|
|
|
@ -909,7 +909,7 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList
|
|||
, ("slash", lit "/")
|
||||
, ("textbf", extractSpaces strong <$> tok)
|
||||
, ("textnormal", extractSpaces (spanWith ("",["nodecor"],[])) <$> tok)
|
||||
, ("underline", underlineSpan <$> tok)
|
||||
, ("underline", underline <$> tok)
|
||||
, ("ldots", lit "…")
|
||||
, ("vdots", lit "\8942")
|
||||
, ("dots", lit "…")
|
||||
|
@ -1171,9 +1171,9 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList
|
|||
-- include
|
||||
, ("input", rawInlineOr "input" $ include "input")
|
||||
-- soul package
|
||||
, ("ul", underlineSpan <$> tok)
|
||||
, ("ul", underline <$> tok)
|
||||
-- ulem package
|
||||
, ("uline", underlineSpan <$> tok)
|
||||
, ("uline", underline <$> tok)
|
||||
-- plain tex stuff that should just be passed through as raw tex
|
||||
, ("ifdim", ifdim)
|
||||
]
|
||||
|
|
|
@ -1751,7 +1751,9 @@ bracketedSpan = try $ do
|
|||
attr <- attributes
|
||||
return $ if isSmallCaps attr
|
||||
then B.smallcaps <$> lab
|
||||
else B.spanWith attr <$> lab
|
||||
else if isUnderline attr
|
||||
then B.underline <$> lab
|
||||
else B.spanWith attr <$> lab
|
||||
|
||||
-- | We treat a span as SmallCaps if class is "smallcaps" (and
|
||||
-- no other attributes are set or if style is "font-variant:small-caps"
|
||||
|
@ -1765,6 +1767,13 @@ isSmallCaps ("",[],kvs) =
|
|||
Nothing -> False
|
||||
isSmallCaps _ = False
|
||||
|
||||
-- | We treat a span as Underline if class is "ul" or
|
||||
-- "underline" (and no other attributes are set).
|
||||
isUnderline :: Attr -> Bool
|
||||
isUnderline ("",["ul"],[]) = True
|
||||
isUnderline ("",["underline"],[]) = True
|
||||
isUnderline _ = False
|
||||
|
||||
regLink :: PandocMonad m
|
||||
=> (Attr -> Text -> Text -> Inlines -> Inlines)
|
||||
-> F Inlines
|
||||
|
@ -1913,7 +1922,9 @@ spanHtml = try $ do
|
|||
let keyvals = [(k,v) | (k,v) <- attrs, k /= "id" && k /= "class"]
|
||||
return $ if isSmallCaps (ident, classes, keyvals)
|
||||
then B.smallcaps <$> contents
|
||||
else B.spanWith (ident, classes, keyvals) <$> contents
|
||||
else if isUnderline (ident, classes, keyvals)
|
||||
then B.underline <$> contents
|
||||
else B.spanWith (ident, classes, keyvals) <$> contents
|
||||
|
||||
divHtml :: PandocMonad m => MarkdownParser m (F Blocks)
|
||||
divHtml = try $ do
|
||||
|
|
|
@ -29,7 +29,7 @@ import qualified Data.Set as Set
|
|||
import Data.Maybe (fromMaybe, isNothing, maybeToList)
|
||||
import Data.Text (Text)
|
||||
import qualified Data.Text as T
|
||||
import Text.Pandoc.Builder (Blocks, Inlines)
|
||||
import Text.Pandoc.Builder (Blocks, Inlines, underline)
|
||||
import qualified Text.Pandoc.Builder as B
|
||||
import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
|
||||
import Text.Pandoc.Definition
|
||||
|
@ -37,7 +37,7 @@ import Text.Pandoc.Error (PandocError (PandocParsecError))
|
|||
import Text.Pandoc.Logging
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Parsing hiding (F)
|
||||
import Text.Pandoc.Shared (crFilter, trimr, underlineSpan, tshow)
|
||||
import Text.Pandoc.Shared (crFilter, trimr, tshow)
|
||||
|
||||
-- | Read Muse from an input string and return a Pandoc document.
|
||||
readMuse :: PandocMonad m
|
||||
|
@ -849,7 +849,7 @@ emph = fmap B.emph <$> emphasisBetween (char '*' <* notFollowedBy (char '*'))
|
|||
-- | Parse underline inline markup, indicated by @_@.
|
||||
-- Supported only in Emacs Muse mode, not Text::Amuse.
|
||||
underlined :: PandocMonad m => MuseParser m (F Inlines)
|
||||
underlined = fmap underlineSpan
|
||||
underlined = fmap underline
|
||||
<$ guardDisabled Ext_amuse -- Supported only by Emacs Muse
|
||||
<*> emphasisBetween (char '_')
|
||||
|
||||
|
|
|
@ -37,7 +37,7 @@ import Data.Semigroup (First(..), Option(..))
|
|||
import Text.TeXMath (readMathML, writeTeX)
|
||||
import qualified Text.XML.Light as XML
|
||||
|
||||
import Text.Pandoc.Builder
|
||||
import Text.Pandoc.Builder hiding (underline)
|
||||
import Text.Pandoc.MediaBag (MediaBag, insertMedia)
|
||||
import Text.Pandoc.Shared
|
||||
import Text.Pandoc.Extensions (extensionsFromList, Extension(..))
|
||||
|
|
|
@ -27,7 +27,6 @@ import Text.Pandoc.Class.PandocMonad (PandocMonad)
|
|||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline)
|
||||
import Text.Pandoc.Shared (underlineSpan)
|
||||
import Text.TeXMath (DisplayType (..), readTeX, writePandoc)
|
||||
import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap
|
||||
|
||||
|
@ -567,7 +566,7 @@ strikeout :: PandocMonad m => OrgParser m (F Inlines)
|
|||
strikeout = fmap B.strikeout <$> emphasisBetween '+'
|
||||
|
||||
underline :: PandocMonad m => OrgParser m (F Inlines)
|
||||
underline = fmap underlineSpan <$> emphasisBetween '_'
|
||||
underline = fmap B.underline <$> emphasisBetween '_'
|
||||
|
||||
verbatim :: PandocMonad m => OrgParser m (F Inlines)
|
||||
verbatim = return . B.code <$> verbatimBetween '='
|
||||
|
|
|
@ -52,7 +52,7 @@ import Text.Pandoc.Options
|
|||
import Text.Pandoc.Parsing
|
||||
import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isInlineTag)
|
||||
import Text.Pandoc.Readers.LaTeX (rawLaTeXBlock, rawLaTeXInline)
|
||||
import Text.Pandoc.Shared (crFilter, trim, underlineSpan, tshow)
|
||||
import Text.Pandoc.Shared (crFilter, trim, tshow)
|
||||
|
||||
-- | Parse a Textile text and return a Pandoc document.
|
||||
readTextile :: PandocMonad m
|
||||
|
@ -451,7 +451,7 @@ inlineMarkup = choice [ simpleInline (string "??") (B.cite [])
|
|||
, simpleInline (string "__") B.emph
|
||||
, simpleInline (char '*') B.strong
|
||||
, simpleInline (char '_') B.emph
|
||||
, simpleInline (char '+') underlineSpan
|
||||
, simpleInline (char '+') B.underline
|
||||
, simpleInline (char '-' <* notFollowedBy (char '-')) B.strikeout
|
||||
, simpleInline (char '^') B.superscript
|
||||
, simpleInline (char '~') B.subscript
|
||||
|
|
|
@ -31,8 +31,7 @@ import Data.Time (defaultTimeLocale)
|
|||
import Text.Pandoc.Definition
|
||||
import Text.Pandoc.Options
|
||||
import Text.Pandoc.Parsing hiding (space, spaces, uri)
|
||||
import Text.Pandoc.Shared (compactify, compactifyDL, crFilter, escapeURI,
|
||||
underlineSpan)
|
||||
import Text.Pandoc.Shared (compactify, compactifyDL, crFilter, escapeURI)
|
||||
|
||||
type T2T = ParserT Text ParserState (Reader T2TMeta)
|
||||
|
||||
|
@ -378,7 +377,7 @@ bold :: T2T Inlines
|
|||
bold = inlineMarkup inline B.strong '*' B.str
|
||||
|
||||
underline :: T2T Inlines
|
||||
underline = inlineMarkup inline underlineSpan '_' B.str
|
||||
underline = inlineMarkup inline B.underline '_' B.str
|
||||
|
||||
strike :: T2T Inlines
|
||||
strike = inlineMarkup inline B.strikeout '-' B.str
|
||||
|
|
|
@ -750,11 +750,12 @@ eastAsianLineBreakFilter = bottomUp go
|
|||
go xs
|
||||
= xs
|
||||
|
||||
-- | Builder for underline.
|
||||
{-# DEPRECATED underlineSpan "Use Text.Pandoc.Builder.underline instead" #-}
|
||||
-- | Builder for underline (deprecated).
|
||||
-- This probably belongs in Builder.hs in pandoc-types.
|
||||
-- Will be replaced once Underline is an element.
|
||||
underlineSpan :: Inlines -> Inlines
|
||||
underlineSpan = B.spanWith ("", ["underline"], [])
|
||||
underlineSpan = B.underline
|
||||
|
||||
-- | Set of HTML elements that are represented as Span with a class equal as
|
||||
-- the element tag itself.
|
||||
|
|
|
@ -433,6 +433,9 @@ inlineToAsciiDoc opts (Emph lst) = do
|
|||
isIntraword <- gets intraword
|
||||
let marker = if isIntraword then "__" else "_"
|
||||
return $ marker <> contents <> marker
|
||||
inlineToAsciiDoc opts (Underline lst) = do
|
||||
contents <- inlineListToAsciiDoc opts lst
|
||||
return $ "+++" <> contents <> "+++"
|
||||
inlineToAsciiDoc opts (Strong lst) = do
|
||||
contents <- inlineListToAsciiDoc opts lst
|
||||
isIntraword <- gets intraword
|
||||
|
|
|
@ -237,6 +237,11 @@ inlineToNodes opts SoftBreak
|
|||
| writerWrapText opts == WrapNone = (node (TEXT " ") [] :)
|
||||
| otherwise = (node SOFTBREAK [] :)
|
||||
inlineToNodes opts (Emph xs) = (node EMPH (inlinesToNodes opts xs) :)
|
||||
inlineToNodes opts (Underline xs)
|
||||
| isEnabled Ext_raw_html opts =
|
||||
((node (HTML_INLINE (T.pack "<u>")) [] : inlinesToNodes opts xs ++
|
||||
[node (HTML_INLINE (T.pack "</u>")) []]) ++ )
|
||||
| otherwise = (node EMPH (inlinesToNodes opts xs) :)
|
||||
inlineToNodes opts (Strong xs) = (node STRONG (inlinesToNodes opts xs) :)
|
||||
inlineToNodes opts (Strikeout xs)
|
||||
| isEnabled Ext_strikeout opts = (node (CUSTOM_INLINE "~~" "~~") (inlinesToNodes opts xs) :)
|
||||
|
|
|
@ -368,6 +368,9 @@ inlineToConTeXt :: PandocMonad m
|
|||
inlineToConTeXt (Emph lst) = do
|
||||
contents <- inlineListToConTeXt lst
|
||||
return $ braces $ "\\em " <> contents
|
||||
inlineToConTeXt (Underline lst) = do
|
||||
contents <- inlineListToConTeXt lst
|
||||
return $ "\\underbar" <> braces contents
|
||||
inlineToConTeXt (Strong lst) = do
|
||||
contents <- inlineListToConTeXt lst
|
||||
return $ braces $ "\\bf " <> contents
|
||||
|
|
|
@ -186,6 +186,8 @@ inlineToCustom SoftBreak = Lua.callFunc "SoftBreak"
|
|||
|
||||
inlineToCustom (Emph lst) = Lua.callFunc "Emph" (Stringify lst)
|
||||
|
||||
inlineToCustom (Underline lst) = Lua.callFunc "Underline" (Stringify lst)
|
||||
|
||||
inlineToCustom (Strong lst) = Lua.callFunc "Strong" (Stringify lst)
|
||||
|
||||
inlineToCustom (Strikeout lst) = Lua.callFunc "Strikeout" (Stringify lst)
|
||||
|
|
|
@ -323,6 +323,8 @@ inlineToDocbook :: PandocMonad m => WriterOptions -> Inline -> DB m (Doc Text)
|
|||
inlineToDocbook _ (Str str) = return $ literal $ escapeStringForXML str
|
||||
inlineToDocbook opts (Emph lst) =
|
||||
inTagsSimple "emphasis" <$> inlinesToDocbook opts lst
|
||||
inlineToDocbook opts (Underline lst) =
|
||||
inTags False "emphasis" [("role", "underline")] <$> inlinesToDocbook opts lst
|
||||
inlineToDocbook opts (Strong lst) =
|
||||
inTags False "emphasis" [("role", "strong")] <$> inlinesToDocbook opts lst
|
||||
inlineToDocbook opts (Strikeout lst) =
|
||||
|
|
|
@ -1158,9 +1158,6 @@ inlineToOpenXML' _ (Str str) =
|
|||
formattedString str
|
||||
inlineToOpenXML' opts Space = inlineToOpenXML opts (Str " ")
|
||||
inlineToOpenXML' opts SoftBreak = inlineToOpenXML opts (Str " ")
|
||||
inlineToOpenXML' opts (Span (_,["underline"],_) ils) =
|
||||
withTextProp (mknode "w:u" [("w:val","single")] ()) $
|
||||
inlinesToOpenXML opts ils
|
||||
inlineToOpenXML' _ (Span (ident,["comment-start"],kvs) ils) = do
|
||||
-- prefer the "id" in kvs, since that is the one produced by the docx
|
||||
-- reader.
|
||||
|
@ -1234,6 +1231,9 @@ inlineToOpenXML' opts (Strong lst) =
|
|||
withTextProp (mknode "w:b" [] ()) $ inlinesToOpenXML opts lst
|
||||
inlineToOpenXML' opts (Emph lst) =
|
||||
withTextProp (mknode "w:i" [] ()) $ inlinesToOpenXML opts lst
|
||||
inlineToOpenXML' opts (Underline lst) =
|
||||
withTextProp (mknode "w:u" [("w:val","single")] ()) $
|
||||
inlinesToOpenXML opts lst
|
||||
inlineToOpenXML' opts (Subscript lst) =
|
||||
withTextProp (mknode "w:vertAlign" [("w:val","subscript")] ())
|
||||
$ inlinesToOpenXML opts lst
|
||||
|
|
|
@ -402,6 +402,10 @@ inlineToDokuWiki opts (Emph lst) = do
|
|||
contents <- inlineListToDokuWiki opts lst
|
||||
return $ "//" <> contents <> "//"
|
||||
|
||||
inlineToDokuWiki opts (Underline lst) = do
|
||||
contents <- inlineListToDokuWiki opts lst
|
||||
return $ "__" <> contents <> "__"
|
||||
|
||||
inlineToDokuWiki opts (Strong lst) = do
|
||||
contents <- inlineListToDokuWiki opts lst
|
||||
return $ "**" <> contents <> "**"
|
||||
|
|
|
@ -406,6 +406,7 @@ toXml :: PandocMonad m => Inline -> FBM m [Content]
|
|||
toXml (Str s) = return [txt s]
|
||||
toXml (Span _ ils) = cMapM toXml ils
|
||||
toXml (Emph ss) = list `liftM` wrap "emphasis" ss
|
||||
toXml (Underline ss) = list `liftM` wrap "underline" ss
|
||||
toXml (Strong ss) = list `liftM` wrap "strong" ss
|
||||
toXml (Strikeout ss) = list `liftM` wrap "strikethrough" ss
|
||||
toXml (Superscript ss) = list `liftM` wrap "sup" ss
|
||||
|
@ -529,6 +530,7 @@ list = (:[])
|
|||
plain :: Inline -> String
|
||||
plain (Str s) = T.unpack s
|
||||
plain (Emph ss) = cMap plain ss
|
||||
plain (Underline ss) = cMap plain ss
|
||||
plain (Span _ ss) = cMap plain ss
|
||||
plain (Strong ss) = cMap plain ss
|
||||
plain (Strikeout ss) = cMap plain ss
|
||||
|
|
|
@ -1049,6 +1049,7 @@ inlineToHtml opts inline = do
|
|||
]
|
||||
|
||||
(Emph lst) -> H.em <$> inlineListToHtml opts lst
|
||||
(Underline lst) -> H.u <$> inlineListToHtml opts lst
|
||||
(Strong lst) -> H.strong <$> inlineListToHtml opts lst
|
||||
(Code attr@(ids,cs,kvs) str)
|
||||
-> case hlCode of
|
||||
|
|
|
@ -209,6 +209,9 @@ inlineToHaddock opts (Span (ident,_,_) ils) = do
|
|||
inlineToHaddock opts (Emph lst) = do
|
||||
contents <- inlineListToHaddock opts lst
|
||||
return $ "/" <> contents <> "/"
|
||||
-- Underline is not supported, treat the same as Emph
|
||||
inlineToHaddock opts (Underline lst) =
|
||||
inlineToHaddock opts (Emph lst)
|
||||
inlineToHaddock opts (Strong lst) = do
|
||||
contents <- inlineListToHaddock opts lst
|
||||
return $ "__" <> contents <> "__"
|
||||
|
|
|
@ -60,6 +60,7 @@ defaultWriterState = WriterState{
|
|||
|
||||
-- inline names (appear in InDesign's character styles pane)
|
||||
emphName :: Text
|
||||
underlineName :: Text
|
||||
strongName :: Text
|
||||
strikeoutName :: Text
|
||||
superscriptName :: Text
|
||||
|
@ -68,6 +69,7 @@ smallCapsName :: Text
|
|||
codeName :: Text
|
||||
linkName :: Text
|
||||
emphName = "Italic"
|
||||
underlineName = "Underline"
|
||||
strongName = "Bold"
|
||||
strikeoutName = "Strikeout"
|
||||
superscriptName = "Superscript"
|
||||
|
@ -427,6 +429,7 @@ inlinesToICML opts style lst = vcat `fmap` mapM (inlineToICML opts style) (merge
|
|||
inlineToICML :: PandocMonad m => WriterOptions -> Style -> Inline -> WS m (Doc Text)
|
||||
inlineToICML _ style (Str str) = charStyle style $ literal $ escapeStringForXML str
|
||||
inlineToICML opts style (Emph lst) = inlinesToICML opts (emphName:style) lst
|
||||
inlineToICML opts style (Underline lst) = inlinesToICML opts (underlineName:style) lst
|
||||
inlineToICML opts style (Strong lst) = inlinesToICML opts (strongName:style) lst
|
||||
inlineToICML opts style (Strikeout lst) = inlinesToICML opts (strikeoutName:style) lst
|
||||
inlineToICML opts style (Superscript lst) = inlinesToICML opts (superscriptName:style) lst
|
||||
|
|
|
@ -424,6 +424,8 @@ inlineToJATS :: PandocMonad m => WriterOptions -> Inline -> JATS m (Doc Text)
|
|||
inlineToJATS _ (Str str) = return $ text $ T.unpack $ escapeStringForXML str
|
||||
inlineToJATS opts (Emph lst) =
|
||||
inTagsSimple "italic" <$> inlinesToJATS opts lst
|
||||
inlineToJATS opts (Underline lst) =
|
||||
inTagsSimple "underline" <$> inlinesToJATS opts lst
|
||||
inlineToJATS opts (Strong lst) =
|
||||
inTagsSimple "bold" <$> inlinesToJATS opts lst
|
||||
inlineToJATS opts (Strikeout lst) =
|
||||
|
|
|
@ -193,6 +193,7 @@ toJiraInlines inlines = do
|
|||
Code _ cs -> return . singleton $
|
||||
Jira.Monospaced (escapeSpecialChars cs)
|
||||
Emph xs -> styled Jira.Emphasis xs
|
||||
Underline xs -> styled Jira.Insert xs
|
||||
Image attr _ tgt -> imageToJira attr (fst tgt) (snd tgt)
|
||||
LineBreak -> pure . singleton $ Jira.Linebreak
|
||||
Link attr xs tgt -> toJiraLink attr tgt xs
|
||||
|
|
|
@ -1140,6 +1140,7 @@ inlineToLaTeX (Span (id',classes,kvs) ils) = do
|
|||
then braces contents
|
||||
else foldr inCmd contents cmds)
|
||||
inlineToLaTeX (Emph lst) = inCmd "emph" <$> inlineListToLaTeX lst
|
||||
inlineToLaTeX (Underline lst) = inCmd "underline" <$> inlineListToLaTeX lst
|
||||
inlineToLaTeX (Strong lst) = inCmd "textbf" <$> inlineListToLaTeX lst
|
||||
inlineToLaTeX (Strikeout lst) = do
|
||||
-- we need to protect VERB in an mbox or we get an error
|
||||
|
|
|
@ -270,6 +270,9 @@ inlineToMan :: PandocMonad m => WriterOptions -> Inline -> StateT WriterState m
|
|||
inlineToMan opts (Span _ ils) = inlineListToMan opts ils
|
||||
inlineToMan opts (Emph lst) =
|
||||
withFontFeature 'I' (inlineListToMan opts lst)
|
||||
-- Underline is not supported, so treat the same as Emph
|
||||
inlineToMan opts (Underline lst) =
|
||||
withFontFeature 'I' (inlineListToMan opts lst)
|
||||
inlineToMan opts (Strong lst) =
|
||||
withFontFeature 'B' (inlineListToMan opts lst)
|
||||
inlineToMan opts (Strikeout lst) = do
|
||||
|
|
|
@ -1045,6 +1045,21 @@ inlineToMarkdown opts (Emph lst) = do
|
|||
then "_" <> contents <> "_"
|
||||
else contents
|
||||
else "*" <> contents <> "*"
|
||||
inlineToMarkdown _ (Underline []) = return empty
|
||||
inlineToMarkdown opts (Underline lst) = do
|
||||
plain <- asks envPlain
|
||||
contents <- inlineListToMarkdown opts lst
|
||||
case plain of
|
||||
True -> return contents
|
||||
False | isEnabled Ext_bracketed_spans opts ->
|
||||
return $ "[" <> contents <> "]" <> "{.ul}"
|
||||
| isEnabled Ext_native_spans opts ->
|
||||
return $ tagWithAttrs "span" ("", ["underline"], [])
|
||||
<> contents
|
||||
<> literal "</span>"
|
||||
| isEnabled Ext_raw_html opts ->
|
||||
return $ "<u>" <> contents <> "</u>"
|
||||
| otherwise -> inlineToMarkdown opts (Emph lst)
|
||||
inlineToMarkdown _ (Strong []) = return empty
|
||||
inlineToMarkdown opts (Strong lst) = do
|
||||
plain <- asks envPlain
|
||||
|
|
|
@ -372,6 +372,10 @@ inlineToMediaWiki (Emph lst) = do
|
|||
contents <- inlineListToMediaWiki lst
|
||||
return $ "''" <> contents <> "''"
|
||||
|
||||
inlineToMediaWiki (Underline lst) = do
|
||||
contents <- inlineListToMediaWiki lst
|
||||
return $ "<u>" <> contents <> "</u>"
|
||||
|
||||
inlineToMediaWiki (Strong lst) = do
|
||||
contents <- inlineListToMediaWiki lst
|
||||
return $ "'''" <> contents <> "'''"
|
||||
|
|
|
@ -351,6 +351,8 @@ inlineToMs :: PandocMonad m => WriterOptions -> Inline -> MS m (Doc Text)
|
|||
inlineToMs opts (Span _ ils) = inlineListToMs opts ils
|
||||
inlineToMs opts (Emph lst) =
|
||||
withFontFeature 'I' (inlineListToMs opts lst)
|
||||
inlineToMs opts (Underline lst) =
|
||||
inlineToMs opts (Emph lst)
|
||||
inlineToMs opts (Strong lst) =
|
||||
withFontFeature 'B' (inlineListToMs opts lst)
|
||||
inlineToMs opts (Strikeout lst) = do
|
||||
|
|
|
@ -594,6 +594,13 @@ inlineToMuse (Strong [Emph lst]) = do
|
|||
else if null lst' || startsWithSpace lst' || endsWithSpace lst'
|
||||
then emphasis "**<em>" "</em>**" lst'
|
||||
else emphasis "***" "***" lst'
|
||||
-- | Underline is only supported in Emacs Muse mode.
|
||||
inlineToMuse (Underline lst) = do
|
||||
opts <- asks envOptions
|
||||
contents <- inlineListToMuse lst
|
||||
if isEnabled Ext_amuse opts
|
||||
then return $ "_" <> contents <> "_"
|
||||
else inlineToMuse (Emph lst)
|
||||
inlineToMuse (Strong lst) = do
|
||||
useTags <- gets stUseTags
|
||||
let lst' = normalizeInlineList lst
|
||||
|
|
|
@ -512,6 +512,7 @@ inlineToOpenDocument o ils
|
|||
LineBreak -> return $ selfClosingTag "text:line-break" []
|
||||
Str s -> return $ handleSpaces $ escapeStringForXML s
|
||||
Emph l -> withTextStyle Italic $ inlinesToOpenDocument o l
|
||||
Underline l -> withTextStyle Under $ inlinesToOpenDocument o l
|
||||
Strong l -> withTextStyle Bold $ inlinesToOpenDocument o l
|
||||
Strikeout l -> withTextStyle Strike $ inlinesToOpenDocument o l
|
||||
Superscript l -> withTextStyle Sup $ inlinesToOpenDocument o l
|
||||
|
@ -692,6 +693,7 @@ paraTableStyles t s (a:xs)
|
|||
|
||||
data TextStyle = Italic
|
||||
| Bold
|
||||
| Under
|
||||
| Strike
|
||||
| Sub
|
||||
| Sup
|
||||
|
@ -710,6 +712,9 @@ textStyleAttr m s
|
|||
| Bold <- s = Map.insert "fo:font-weight" "bold" .
|
||||
Map.insert "style:font-weight-asian" "bold" .
|
||||
Map.insert "style:font-weight-complex" "bold" $ m
|
||||
| Under <- s = Map.insert "style:text-underline-style" "solid" .
|
||||
Map.insert "style:text-underline-width" "auto" .
|
||||
Map.insert "style:text-underline-color" "font-color" $ m
|
||||
| Strike <- s = Map.insert "style:text-line-through-style" "solid" m
|
||||
| Sub <- s = Map.insert "style:text-position" "sub 58%" m
|
||||
| Sup <- s = Map.insert "style:text-position" "super 58%" m
|
||||
|
|
|
@ -329,6 +329,9 @@ inlineToOrg (Span _ lst) =
|
|||
inlineToOrg (Emph lst) = do
|
||||
contents <- inlineListToOrg lst
|
||||
return $ "/" <> contents <> "/"
|
||||
inlineToOrg (Underline lst) = do
|
||||
contents <- inlineListToOrg lst
|
||||
return $ "_" <> contents <> "_"
|
||||
inlineToOrg (Strong lst) = do
|
||||
contents <- inlineListToOrg lst
|
||||
return $ "*" <> contents <> "*"
|
||||
|
|
|
@ -323,6 +323,9 @@ inlineToParElems (Str s) = do
|
|||
inlineToParElems (Emph ils) =
|
||||
local (\r -> r{envRunProps = (envRunProps r){rPropItalics=True}}) $
|
||||
inlinesToParElems ils
|
||||
inlineToParElems (Underline ils) =
|
||||
local (\r -> r{envRunProps = (envRunProps r){rPropUnderline=True}}) $
|
||||
inlinesToParElems ils
|
||||
inlineToParElems (Strong ils) =
|
||||
local (\r -> r{envRunProps = (envRunProps r){rPropBold=True}}) $
|
||||
inlinesToParElems ils
|
||||
|
|
|
@ -415,6 +415,7 @@ transformInlines = insertBS .
|
|||
hasContents :: Inline -> Bool
|
||||
hasContents (Str "") = False
|
||||
hasContents (Emph []) = False
|
||||
hasContents (Underline []) = False
|
||||
hasContents (Strong []) = False
|
||||
hasContents (Strikeout []) = False
|
||||
hasContents (Superscript []) = False
|
||||
|
@ -474,6 +475,7 @@ transformInlines = insertBS .
|
|||
okBeforeComplex _ = False
|
||||
isComplex :: Inline -> Bool
|
||||
isComplex (Emph _) = True
|
||||
isComplex (Underline _) = True
|
||||
isComplex (Strong _) = True
|
||||
isComplex (SmallCaps _) = True
|
||||
isComplex (Strikeout _) = True
|
||||
|
@ -538,6 +540,7 @@ mapNested f i = setInlineChildren i (f (dropInlineParent i))
|
|||
dropInlineParent :: Inline -> [Inline]
|
||||
dropInlineParent (Link _ i _) = i
|
||||
dropInlineParent (Emph i) = i
|
||||
dropInlineParent (Underline i) = i
|
||||
dropInlineParent (Strong i) = i
|
||||
dropInlineParent (Strikeout i) = i
|
||||
dropInlineParent (Superscript i) = i
|
||||
|
@ -552,6 +555,7 @@ dropInlineParent i = [i] -- not a parent, like Str or Space
|
|||
setInlineChildren :: Inline -> [Inline] -> Inline
|
||||
setInlineChildren (Link a _ t) i = Link a i t
|
||||
setInlineChildren (Emph _) i = Emph i
|
||||
setInlineChildren (Underline _) i = Underline i
|
||||
setInlineChildren (Strong _) i = Strong i
|
||||
setInlineChildren (Strikeout _) i = Strikeout i
|
||||
setInlineChildren (Superscript _) i = Superscript i
|
||||
|
@ -582,6 +586,9 @@ inlineToRST (Span (_,_,kvs) ils) = do
|
|||
inlineToRST (Emph lst) = do
|
||||
contents <- writeInlines lst
|
||||
return $ "*" <> contents <> "*"
|
||||
-- Underline is not supported, fall back to Emph
|
||||
inlineToRST (Underline lst) =
|
||||
inlineToRST (Emph lst)
|
||||
inlineToRST (Strong lst) = do
|
||||
contents <- writeInlines lst
|
||||
return $ "**" <> contents <> "**"
|
||||
|
|
|
@ -351,6 +351,9 @@ inlineToRTF (Span _ lst) = inlinesToRTF lst
|
|||
inlineToRTF (Emph lst) = do
|
||||
contents <- inlinesToRTF lst
|
||||
return $ "{\\i " <> contents <> "}"
|
||||
inlineToRTF (Underline lst) = do
|
||||
contents <- inlinesToRTF lst
|
||||
return $ "{\\pnul " <> contents <> "}"
|
||||
inlineToRTF (Strong lst) = do
|
||||
contents <- inlinesToRTF lst
|
||||
return $ "{\\b " <> contents <> "}"
|
||||
|
|
|
@ -231,6 +231,8 @@ inlineToTEI :: PandocMonad m => WriterOptions -> Inline -> m (Doc Text)
|
|||
inlineToTEI _ (Str str) = return $ literal $ escapeStringForXML str
|
||||
inlineToTEI opts (Emph lst) =
|
||||
inTags False "hi" [("rendition","simple:italic")] <$> inlinesToTEI opts lst
|
||||
inlineToTEI opts (Underline lst) =
|
||||
inTags False "hi" [("rendition","simple:underline")] <$> inlinesToTEI opts lst
|
||||
inlineToTEI opts (Strong lst) =
|
||||
inTags False "hi" [("rendition", "simple:bold")] <$> inlinesToTEI opts lst
|
||||
inlineToTEI opts (Strikeout lst) =
|
||||
|
|
|
@ -392,6 +392,10 @@ inlineToTexinfo (Span _ lst) =
|
|||
inlineToTexinfo (Emph lst) =
|
||||
inCmd "emph" <$> inlineListToTexinfo lst
|
||||
|
||||
-- Underline isn't supported, fall back to Emph
|
||||
inlineToTexinfo (Underline lst) =
|
||||
inlineToTexinfo (Emph lst)
|
||||
|
||||
inlineToTexinfo (Strong lst) =
|
||||
inCmd "strong" <$> inlineListToTexinfo lst
|
||||
|
||||
|
|
|
@ -386,6 +386,12 @@ inlineToTextile opts (Emph lst) = do
|
|||
then "<em>" <> contents <> "</em>"
|
||||
else "_" <> contents <> "_"
|
||||
|
||||
inlineToTextile opts (Underline lst) = do
|
||||
contents <- inlineListToTextile opts lst
|
||||
return $ if '+' `elemText` contents
|
||||
then "<u>" <> contents <> "</u>"
|
||||
else "+" <> contents <> "+"
|
||||
|
||||
inlineToTextile opts (Strong lst) = do
|
||||
contents <- inlineListToTextile opts lst
|
||||
return $ if '*' `elemText` contents
|
||||
|
|
|
@ -163,6 +163,10 @@ inlineToXWiki (Emph lst) = do
|
|||
contents <- inlineListToXWiki lst
|
||||
return $ "//" <> contents <> "//"
|
||||
|
||||
inlineToXWiki (Underline lst) = do
|
||||
contents <- inlineListToXWiki lst
|
||||
return $ "__" <> contents <> "__"
|
||||
|
||||
inlineToXWiki (Strong lst) = do
|
||||
contents <- inlineListToXWiki lst
|
||||
return $ "**" <> contents <> "**"
|
||||
|
|
|
@ -273,6 +273,10 @@ inlineToZimWiki opts (Emph lst) = do
|
|||
contents <- inlineListToZimWiki opts lst
|
||||
return $ "//" <> contents <> "//"
|
||||
|
||||
inlineToZimWiki opts (Underline lst) = do
|
||||
contents <- inlineListToZimWiki opts lst
|
||||
return $ "__" <> contents <> "__"
|
||||
|
||||
inlineToZimWiki opts (Strong lst) = do
|
||||
contents <- inlineListToZimWiki opts lst
|
||||
return $ "**" <> contents <> "**"
|
||||
|
|
|
@ -22,7 +22,6 @@ import Tests.Helpers
|
|||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
import Text.Pandoc.Builder
|
||||
import Text.Pandoc.Shared (underlineSpan)
|
||||
|
||||
dokuwiki :: Text -> Pandoc
|
||||
dokuwiki = purely $ readDokuWiki def{ readerStandalone = True }
|
||||
|
@ -42,7 +41,7 @@ tests = [ testGroup "inlines"
|
|||
para (emph "italic")
|
||||
, "Underlined" =:
|
||||
"__underlined__" =?>
|
||||
para (underlineSpan "underlined")
|
||||
para (underline "underlined")
|
||||
, "Monospaced" =:
|
||||
"''monospaced''" =?>
|
||||
para (code "monospaced")
|
||||
|
@ -51,7 +50,7 @@ tests = [ testGroup "inlines"
|
|||
para (code "monospaced")
|
||||
, "Combined" =:
|
||||
"**__//''combine''//__**" =?>
|
||||
para (strong $ underlineSpan $ emph $ code "combine")
|
||||
para (strong $ underline $ emph $ code "combine")
|
||||
, "Nowiki" =:
|
||||
T.unlines [ "<nowiki>"
|
||||
, "This is some text which contains addresses like this: http://www.splitbrain.org and **formatting**, but nothing is done with it."
|
||||
|
|
|
@ -25,7 +25,6 @@ import Tests.Helpers
|
|||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
import Text.Pandoc.Builder
|
||||
import Text.Pandoc.Shared (underlineSpan)
|
||||
import Text.Pandoc.Writers.Shared (toLegacyTable)
|
||||
import Text.Pandoc.Walk
|
||||
|
||||
|
@ -209,7 +208,7 @@ tests =
|
|||
para (strong . emph $ "foo******bar")
|
||||
|
||||
, test emacsMuse "Underline"
|
||||
("_Underline_" =?> para (underlineSpan "Underline"))
|
||||
("_Underline_" =?> para (underline "Underline"))
|
||||
|
||||
, "Superscript tag" =: "<sup>Superscript</sup>" =?> para (superscript "Superscript")
|
||||
|
||||
|
|
|
@ -19,7 +19,6 @@ import Test.Tasty (TestTree, testGroup)
|
|||
import Tests.Helpers ((=?>))
|
||||
import Tests.Readers.Org.Shared ((=:), spcSep)
|
||||
import Text.Pandoc.Builder
|
||||
import Text.Pandoc.Shared (underlineSpan)
|
||||
import qualified Data.Text as T
|
||||
import qualified Tests.Readers.Org.Inline.Citation as Citation
|
||||
import qualified Tests.Readers.Org.Inline.Note as Note
|
||||
|
@ -49,7 +48,7 @@ tests =
|
|||
|
||||
, "Underline" =:
|
||||
"_underline_" =?>
|
||||
para (underlineSpan "underline")
|
||||
para (underline "underline")
|
||||
|
||||
, "Strikeout" =:
|
||||
"+Kill Bill+" =?>
|
||||
|
|
|
@ -23,7 +23,6 @@ import Tests.Helpers
|
|||
import Text.Pandoc
|
||||
import Text.Pandoc.Arbitrary ()
|
||||
import Text.Pandoc.Builder
|
||||
import Text.Pandoc.Shared (underlineSpan)
|
||||
|
||||
t2t :: Text -> Pandoc
|
||||
-- t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def
|
||||
|
@ -94,12 +93,12 @@ tests =
|
|||
|
||||
, "Inline markup is greedy" =:
|
||||
"***** ///// _____ ----- ````` \"\"\"\"\" '''''" =?>
|
||||
para (spcSep [strong "*", emph "/", underlineSpan "_"
|
||||
para (spcSep [strong "*", emph "/", underline "_"
|
||||
, strikeout "-", code "`", text "\""
|
||||
, rawInline "html" "'"])
|
||||
, "Markup must be greedy" =:
|
||||
"********** ////////// __________ ---------- `````````` \"\"\"\"\"\"\"\"\"\" ''''''''''" =?>
|
||||
para (spcSep [strong "******", emph "//////", underlineSpan "______"
|
||||
para (spcSep [strong "******", emph "//////", underline "______"
|
||||
, strikeout "------", code "``````", text "\"\"\"\"\"\""
|
||||
, rawInline "html" "''''''"])
|
||||
, "Inlines must be glued" =:
|
||||
|
|
|
@ -1,2 +1,3 @@
|
|||
Pandoc (Meta {unMeta = fromList []})
|
||||
[Header 1 ("test",[],[]) [Str "Test"]
|
||||
,Para [Str "This",Space,Str "is",Space,Emph [Str "italic"],Str ",",Space,Strong [Str "bold"],Str ",",Space,Span ("",["underline"],[]) [Str "underlined"],Str ",",Space,Emph [Span ("",["underline"],[]) [Str "italic",Space,Str "underlined"]],Str ",",Space,Strong [Span ("",["underline"],[]) [Str "bold",Space,Str "underlined"]],Str ",",Space,Emph [Strong [Span ("",["underline"],[]) [Str "bold",Space,Str "italic",Space,Str "underlined"]]],Str "."]]
|
||||
,Para [Str "This",Space,Str "is",Space,Emph [Str "italic"],Str ",",Space,Strong [Str "bold"],Str ",",Space,Underline [Str "underlined"],Str ",",Space,Emph [Underline [Str "italic",Space,Str "underlined"]],Str ",",Space,Strong [Underline [Str "bold",Space,Str "underlined"]],Str ",",Space,Emph [Strong [Underline [Str "bold",Space,Str "italic",Space,Str "underlined"]]],Str "."]]
|
||||
|
|
Binary file not shown.
|
@ -1,5 +1,6 @@
|
|||
Pandoc (Meta {unMeta = fromList []})
|
||||
[Para [Str "Regular",Space,Str "text",Space,Emph [Str "italics"],Space,Strong [Str "bold",Space,Emph [Str "bold",Space,Str "italics"]],Str "."]
|
||||
,Para [Str "This",Space,Str "is",Space,SmallCaps [Str "Small",Space,Str "Caps"],Str ",",Space,Str "and",Space,Str "this",Space,Str "is",Space,Strikeout [Str "strikethrough"],Str "."]
|
||||
,Para [Str "Some",Space,Str "people",Space,Str "use",Space,Span ("",["underline"],[]) [Str "single",Space,Str "underlines",Space,Str "for",Space,Emph [Str "emphasis"]],Str "."]
|
||||
,Para [Str "Some",Space,Str "people",Space,Str "use",Space,Underline [Str "single",Space,Str "underlines",Space,Str "for",Space],Emph [Underline [Str "emphasis"]],Str "."]
|
||||
,Para [Str "Above",Space,Str "the",Space,Str "line",Space,Str "is",Space,Superscript [Str "superscript"],Space,Str "and",Space,Str "below",Space,Str "the",Space,Str "line",Space,Str "is",Space,Subscript [Str "subscript"],Str "."]
|
||||
,Para [Str "A",Space,Str "line",LineBreak,Str "break."]]
|
||||
|
|
|
@ -211,7 +211,7 @@ Pandoc (Meta {unMeta = fromList [("generator",MetaInlines [Str "pandoc"]),("titl
|
|||
,Para [Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word."]
|
||||
,Para [Str "This",Space,Str "is",Space,Str "code:",Space,Code ("",[],[]) ">",Str ",",Space,Code ("",[],[]) "$",Str ",",Space,Code ("",[],[]) "\\",Str ",",Space,Code ("",[],[]) "\\$",Str ",",Space,Code ("",[],[]) "<html>",Str "."]
|
||||
,Para [Str "This",Space,Str "is",Space,SmallCaps [Str "small",Space,Str "caps"],Str "."]
|
||||
,Para [Str "These",Space,Str "are",Space,Str "all",Space,Str "underlined:",Space,Span ("",["underline"],[]) [Str "foo"],Space,Str "and",Space,Span ("",["underline"],[]) [Str "bar"],Str "."]
|
||||
,Para [Str "These",Space,Str "are",Space,Str "all",Space,Str "underlined:",Space,Underline [Str "foo"],Space,Str "and",Space,Underline [Str "bar"],Str "."]
|
||||
,Para [Str "These",Space,Str "are",Space,Str "all",Space,Str "strikethrough:",Space,Strikeout [Str "foo"],Str ",",Space,Strikeout [Str "bar"],Str ",",Space,Str "and",Space,Strikeout [Str "baz"],Str "."]
|
||||
,HorizontalRule
|
||||
,Header 1 ("smart-quotes-ellipses-dashes",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"]
|
||||
|
|
|
@ -86,7 +86,7 @@ Pandoc (Meta {unMeta = fromList []})
|
|||
,([Str "beer"],
|
||||
[[Plain [Str "fresh",Space,Str "and",Space,Str "bitter"]]])]
|
||||
,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"]
|
||||
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Span ("",["underline"],[]) [Str "inserted"],Str ",",Space,Str "and",Space,Str "this",Space,Str "is",Space,Strikeout [Str "deleted"],Str ".",LineBreak,Str "Hyphenated-words-are-ok,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "strange_underscore_notation.",LineBreak,Str "A",Space,Link ("",[],[]) [Strong [Str "strong",Space,Str "link"]] ("http://www.foobar.com",""),Str "."]
|
||||
,Para [Str "This",Space,Str "is",Space,Emph [Str "emphasized"],Str ",",Space,Str "and",Space,Str "so",Space,Emph [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Strong [Str "strong"],Str ",",Space,Str "and",Space,Str "so",Space,Strong [Str "is",Space,Str "this"],Str ".",LineBreak,Str "This",Space,Str "is",Space,Underline [Str "inserted"],Str ",",Space,Str "and",Space,Str "this",Space,Str "is",Space,Strikeout [Str "deleted"],Str ".",LineBreak,Str "Hyphenated-words-are-ok,",Space,Str "as",Space,Str "well",Space,Str "as",Space,Str "strange_underscore_notation.",LineBreak,Str "A",Space,Link ("",[],[]) [Strong [Str "strong",Space,Str "link"]] ("http://www.foobar.com",""),Str "."]
|
||||
,Para [Emph [Strong [Str "This",Space,Str "is",Space,Str "strong",Space,Str "and",Space,Str "em."]],LineBreak,Str "So",Space,Str "is",Space,Strong [Emph [Str "this"]],Space,Str "word",Space,Str "and",Space,Emph [Strong [Str "that",Space,Str "one"]],Str ".",LineBreak,Strikeout [Str "This",Space,Str "is",Space,Str "strikeout",Space,Str "and",Space,Strong [Str "strong"]]]
|
||||
,Para [Str "Superscripts:",Space,Str "a",Superscript [Str "bc"],Str "d",Space,Str "a",Space,Superscript [Strong [Str "hello"]],Space,Str "a",Superscript [Str "hello",Space,Str "there"],Str ".",LineBreak,Str "Subscripts:",Space,Subscript [Str "here"],Space,Str "H",Space,Subscript [Str "2"],Str "O,",Space,Str "H",Space,Subscript [Str "23"],Str "O,",Space,Str "H",Space,Subscript [Str "many",Space,Str "of",Space,Str "them"],Str "O."]
|
||||
,Para [Str "Dashes",Space,Str ":",Space,Str "How",Space,Str "cool",Space,Str "\8212",Space,Str "automatic",Space,Str "dashes."]
|
||||
|
|
|
@ -29,8 +29,8 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
|
|||
,Para [Strikeout [Str "-------+--------"]]
|
||||
,Para [Str "(",Space,Strikeout [Str "----------------"],Space,Str ")"]
|
||||
,Header 1 ("inline",[],[]) [Str "Inline"]
|
||||
,Para [Str "i)",Space,Strong [Str "b"],Space,Emph [Str "i"],Space,Span ("",["underline"],[]) [Str "u"],Space,Strikeout [Str "s"],Space,Code ("",[],[]) "m",Space,Str "r",Space,RawInline (Format "html") "t",SoftBreak,Str "i)",Space,Strong [Str "bo"],Space,Emph [Str "it"],Space,Span ("",["underline"],[]) [Str "un"],Space,Strikeout [Str "st"],Space,Code ("",[],[]) "mo",Space,Str "ra",Space,RawInline (Format "html") "tg",SoftBreak,Str "i)",Space,Strong [Str "bold"],Space,Emph [Str "ital"],Space,Span ("",["underline"],[]) [Str "undr"],Space,Strikeout [Str "strk"],Space,Code ("",[],[]) "mono",Space,Str "raw",Space,RawInline (Format "html") "tggd",SoftBreak,Str "i)",Space,Strong [Str "bo",Space,Str "ld"],Space,Emph [Str "it",Space,Str "al"],Space,Span ("",["underline"],[]) [Str "un",Space,Str "dr"],Space,Strikeout [Str "st",Space,Str "rk"],Space,Code ("",[],[]) "mo no",Space,Str "r",Space,Str "aw",Space,RawInline (Format "html") "tg gd",SoftBreak,Str "i)",Space,Strong [Str "bo",Space,Str "*",Space,Str "ld"],Space,Emph [Str "it",Space,Str "/",Space,Str "al"],Space,Span ("",["underline"],[]) [Str "un",Space,Str "_",Space,Str "dr"],Space,Strikeout [Str "st",Space,Str "-",Space,Str "rk"],Space,Code ("",[],[]) "mo ` no",Space,Str "r",Space,Str "\"",Space,Str "aw",Space,RawInline (Format "html") "tg ' gd",SoftBreak,Str "i)",Space,Strong [Str "bo",Space,Str "**ld"],Space,Emph [Str "it",Space,Str "//al"],Space,Span ("",["underline"],[]) [Str "un",Space,Str "__dr"],Space,Strikeout [Str "st",Space,Str "--rk"],Space,Code ("",[],[]) "mo ``no",Space,Str "r",Space,Str "\"\"aw",Space,RawInline (Format "html") "tg ''gd",SoftBreak,Str "i)",Space,Strong [Str "bo",Space,Str "**",Space,Str "ld"],Space,Emph [Str "it",Space,Str "//",Space,Str "al"],Space,Span ("",["underline"],[]) [Str "un",Space,Str "__",Space,Str "dr"],Space,Strikeout [Str "st",Space,Str "--",Space,Str "rk"],Space,Code ("",[],[]) "mo `` no",Space,Str "r",Space,Str "\"\"",Space,Str "aw",Space,RawInline (Format "html") "tg '' gd",SoftBreak,Str "i)",Space,Strong [Str "**bold**"],Space,Emph [Str "//ital//"],Space,Span ("",["underline"],[]) [Str "__undr__"],Space,Strikeout [Str "--strk--"],Space,Code ("",[],[]) "``mono``",Space,Str "\"\"raw\"\"",Space,RawInline (Format "html") "''tggd''",SoftBreak,Str "i)",Space,Strong [Str "*bold*"],Space,Emph [Str "/ital/"],Space,Span ("",["underline"],[]) [Str "_undr_"],Space,Strikeout [Str "-strk-"],Space,Code ("",[],[]) "`mono`",Space,Str "\"raw\"",Space,RawInline (Format "html") "'tggd'"]
|
||||
,Para [Str "i)",Space,Strong [Str "*"],Space,Emph [Str "/"],Space,Span ("",["underline"],[]) [Str "_"],Space,Strikeout [Str "-"],Space,Code ("",[],[]) "`",Space,Str "\"",Space,RawInline (Format "html") "'",SoftBreak,Str "i)",Space,Strong [Str "**"],Space,Emph [Str "//"],Space,Span ("",["underline"],[]) [Str "__"],Space,Strikeout [Str "--"],Space,Code ("",[],[]) "``",Space,Str "\"\"",Space,RawInline (Format "html") "''",SoftBreak,Str "i)",Space,Strong [Str "***"],Space,Emph [Str "///"],Space,Span ("",["underline"],[]) [Str "___"],Space,Strikeout [Str "---"],Space,Code ("",[],[]) "```",Space,Str "\"\"\"",Space,RawInline (Format "html") "'''",SoftBreak,Str "i)",Space,Strong [Str "****"],Space,Emph [Str "////"],Space,Span ("",["underline"],[]) [Str "____"],Space,Strikeout [Str "----"],Space,Code ("",[],[]) "````",Space,Str "\"\"\"\"",Space,RawInline (Format "html") "''''",SoftBreak,Str "i)",Space,Strong [Str "*****"],Space,Emph [Str "/////"],Space,Span ("",["underline"],[]) [Str "_____"],Space,Strikeout [Str "-----"],Space,Code ("",[],[]) "`````",Space,Str "\"\"\"\"\"",Space,RawInline (Format "html") "'''''",SoftBreak,Str "i)",Space,Strong [Str "******"],Space,Emph [Str "//////"],Space,Span ("",["underline"],[]) [Str "______"],Space,Strikeout [Str "------"],Space,Code ("",[],[]) "``````",Space,Str "\"\"\"\"\"\"",Space,RawInline (Format "html") "''''''"]
|
||||
,Para [Str "i)",Space,Strong [Str "b"],Space,Emph [Str "i"],Space,Underline [Str "u"],Space,Strikeout [Str "s"],Space,Code ("",[],[]) "m",Space,Str "r",Space,RawInline (Format "html") "t",SoftBreak,Str "i)",Space,Strong [Str "bo"],Space,Emph [Str "it"],Space,Underline [Str "un"],Space,Strikeout [Str "st"],Space,Code ("",[],[]) "mo",Space,Str "ra",Space,RawInline (Format "html") "tg",SoftBreak,Str "i)",Space,Strong [Str "bold"],Space,Emph [Str "ital"],Space,Underline [Str "undr"],Space,Strikeout [Str "strk"],Space,Code ("",[],[]) "mono",Space,Str "raw",Space,RawInline (Format "html") "tggd",SoftBreak,Str "i)",Space,Strong [Str "bo",Space,Str "ld"],Space,Emph [Str "it",Space,Str "al"],Space,Underline [Str "un",Space,Str "dr"],Space,Strikeout [Str "st",Space,Str "rk"],Space,Code ("",[],[]) "mo no",Space,Str "r",Space,Str "aw",Space,RawInline (Format "html") "tg gd",SoftBreak,Str "i)",Space,Strong [Str "bo",Space,Str "*",Space,Str "ld"],Space,Emph [Str "it",Space,Str "/",Space,Str "al"],Space,Underline [Str "un",Space,Str "_",Space,Str "dr"],Space,Strikeout [Str "st",Space,Str "-",Space,Str "rk"],Space,Code ("",[],[]) "mo ` no",Space,Str "r",Space,Str "\"",Space,Str "aw",Space,RawInline (Format "html") "tg ' gd",SoftBreak,Str "i)",Space,Strong [Str "bo",Space,Str "**ld"],Space,Emph [Str "it",Space,Str "//al"],Space,Underline [Str "un",Space,Str "__dr"],Space,Strikeout [Str "st",Space,Str "--rk"],Space,Code ("",[],[]) "mo ``no",Space,Str "r",Space,Str "\"\"aw",Space,RawInline (Format "html") "tg ''gd",SoftBreak,Str "i)",Space,Strong [Str "bo",Space,Str "**",Space,Str "ld"],Space,Emph [Str "it",Space,Str "//",Space,Str "al"],Space,Underline [Str "un",Space,Str "__",Space,Str "dr"],Space,Strikeout [Str "st",Space,Str "--",Space,Str "rk"],Space,Code ("",[],[]) "mo `` no",Space,Str "r",Space,Str "\"\"",Space,Str "aw",Space,RawInline (Format "html") "tg '' gd",SoftBreak,Str "i)",Space,Strong [Str "**bold**"],Space,Emph [Str "//ital//"],Space,Underline [Str "__undr__"],Space,Strikeout [Str "--strk--"],Space,Code ("",[],[]) "``mono``",Space,Str "\"\"raw\"\"",Space,RawInline (Format "html") "''tggd''",SoftBreak,Str "i)",Space,Strong [Str "*bold*"],Space,Emph [Str "/ital/"],Space,Underline [Str "_undr_"],Space,Strikeout [Str "-strk-"],Space,Code ("",[],[]) "`mono`",Space,Str "\"raw\"",Space,RawInline (Format "html") "'tggd'"]
|
||||
,Para [Str "i)",Space,Strong [Str "*"],Space,Emph [Str "/"],Space,Underline [Str "_"],Space,Strikeout [Str "-"],Space,Code ("",[],[]) "`",Space,Str "\"",Space,RawInline (Format "html") "'",SoftBreak,Str "i)",Space,Strong [Str "**"],Space,Emph [Str "//"],Space,Underline [Str "__"],Space,Strikeout [Str "--"],Space,Code ("",[],[]) "``",Space,Str "\"\"",Space,RawInline (Format "html") "''",SoftBreak,Str "i)",Space,Strong [Str "***"],Space,Emph [Str "///"],Space,Underline [Str "___"],Space,Strikeout [Str "---"],Space,Code ("",[],[]) "```",Space,Str "\"\"\"",Space,RawInline (Format "html") "'''",SoftBreak,Str "i)",Space,Strong [Str "****"],Space,Emph [Str "////"],Space,Underline [Str "____"],Space,Strikeout [Str "----"],Space,Code ("",[],[]) "````",Space,Str "\"\"\"\"",Space,RawInline (Format "html") "''''",SoftBreak,Str "i)",Space,Strong [Str "*****"],Space,Emph [Str "/////"],Space,Underline [Str "_____"],Space,Strikeout [Str "-----"],Space,Code ("",[],[]) "`````",Space,Str "\"\"\"\"\"",Space,RawInline (Format "html") "'''''",SoftBreak,Str "i)",Space,Strong [Str "******"],Space,Emph [Str "//////"],Space,Underline [Str "______"],Space,Strikeout [Str "------"],Space,Code ("",[],[]) "``````",Space,Str "\"\"\"\"\"\"",Space,RawInline (Format "html") "''''''"]
|
||||
,Para [Str "i)",Space,Str "****",Space,Str "////",Space,Str "____",Space,Str "----",Space,Str "````",Space,Str "\"\"\"\"",Space,Str "''''",SoftBreak,Str "i)",Space,Str "**",Space,Str "**",Space,Str "//",Space,Str "//",Space,Str "__",Space,Str "__",Space,Str "--",Space,Str "--",Space,Str "``",Space,Str "``",Space,Str "\"\"",Space,Str "\"\"",Space,Str "''",Space,Str "''"]
|
||||
,Para [Str "i)",Space,Str "**",Space,Str "bold**",Space,Str "//",Space,Str "ital//",Space,Str "__",Space,Str "undr__",Space,Str "--",Space,Str "strk--",Space,Str "``",Space,Str "mono``",Space,Str "\"\"",Space,Str "raw\"\"",Space,Str "''",Space,Str "tggd''",SoftBreak,Str "i)",Space,Str "**bold",Space,Str "**",Space,Str "//ital",Space,Str "//",Space,Str "__undr",Space,Str "__",Space,Str "--strk",Space,Str "--",Space,Str "``mono",Space,Str "``",Space,Str "\"\"raw",Space,Str "\"\"",Space,Str "''tggd",Space,Str "''",SoftBreak,Str "i)",Space,Str "**",Space,Str "bold",Space,Str "**",Space,Str "//",Space,Str "ital",Space,Str "//",Space,Str "__",Space,Str "undr",Space,Str "__",Space,Str "--",Space,Str "strk",Space,Str "--",Space,Str "``",Space,Str "mono",Space,Str "``",Space,Str "\"\"",Space,Str "raw",Space,Str "\"\"",Space,Str "''",Space,Str "tggd",Space,Str "''"]
|
||||
,Header 1 ("link",[],[]) [Str "Link"]
|
||||
|
|
Loading…
Reference in a new issue