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:
Vaibhav Sagar 2020-04-28 22:53:06 +08:00 committed by GitHub
parent 8d09a92d97
commit 9c2b659eeb
No known key found for this signature in database
GPG key ID: 4AEE18F83AFDEB23
53 changed files with 169 additions and 45 deletions

View file

@ -829,13 +829,23 @@ M.Subscript = M.Inline:create_constructor(
--- Creates a Superscript inline element --- Creates a Superscript inline element
-- @function Superscript -- @function Superscript
-- @tparam {Inline,..} content inline content -- @tparam {Inline,..} content inline content
-- @treturn Inline strong element -- @treturn Inline superscript element
M.Superscript = M.Inline:create_constructor( M.Superscript = M.Inline:create_constructor(
"Superscript", "Superscript",
function(content) return {c = ensureInlineList(content)} end, function(content) return {c = ensureInlineList(content)} end,
"content" "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 -- Element components

View file

@ -303,6 +303,7 @@ pushInline = \case
Cite citations lst -> pushViaConstructor "Cite" lst citations Cite citations lst -> pushViaConstructor "Cite" lst citations
Code attr lst -> pushViaConstructor "Code" lst (LuaAttr attr) Code attr lst -> pushViaConstructor "Code" lst (LuaAttr attr)
Emph inlns -> pushViaConstructor "Emph" inlns Emph inlns -> pushViaConstructor "Emph" inlns
Underline inlns -> pushViaConstructor "Underline" inlns
Image attr alt (src,tit) -> pushViaConstructor "Image" alt src tit (LuaAttr attr) Image attr alt (src,tit) -> pushViaConstructor "Image" alt src tit (LuaAttr attr)
LineBreak -> pushViaConstructor "LineBreak" LineBreak -> pushViaConstructor "LineBreak"
Link attr lst (src,tit) -> pushViaConstructor "Link" lst src tit (LuaAttr attr) 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 "Cite" -> uncurry Cite <$> elementContent
"Code" -> withAttr Code <$> elementContent "Code" -> withAttr Code <$> elementContent
"Emph" -> Emph <$> elementContent "Emph" -> Emph <$> elementContent
"Underline" -> Underline <$> elementContent
"Image" -> (\(LuaAttr attr, lst, tgt) -> Image attr lst tgt) "Image" -> (\(LuaAttr attr, lst, tgt) -> Image attr lst tgt)
<$> elementContent <$> elementContent
"Link" -> (\(LuaAttr attr, lst, tgt) -> Link attr lst tgt) "Link" -> (\(LuaAttr attr, lst, tgt) -> Link attr lst tgt)

View file

@ -299,7 +299,7 @@ runStyleToTransform rPr
return $ subscript . transform return $ subscript . transform
| Just "single" <- rUnderline rPr = do | Just "single" <- rUnderline rPr = do
transform <- runStyleToTransform rPr{rUnderline = Nothing} transform <- runStyleToTransform rPr{rUnderline = Nothing}
return $ underlineSpan . transform return $ Pandoc.underline . transform
| otherwise = return id | otherwise = return id
runToInlines :: PandocMonad m => Run -> DocxContext m Inlines runToInlines :: PandocMonad m => Run -> DocxContext m Inlines

View file

@ -29,7 +29,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Error (PandocError (PandocParsecError)) import Text.Pandoc.Error (PandocError (PandocParsecError))
import Text.Pandoc.Options import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (enclosed, nested) 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. -- | Read DokuWiki from an input string and return a Pandoc document.
readDokuWiki :: PandocMonad m readDokuWiki :: PandocMonad m
@ -162,7 +162,7 @@ italic :: PandocMonad m => DWParser m B.Inlines
italic = try $ B.emph <$> enclosed (string "//") nestedInlines italic = try $ B.emph <$> enclosed (string "//") nestedInlines
underlined :: PandocMonad m => DWParser m B.Inlines 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 :: PandocMonad m => DWParser m B.Inlines
nowiki = try $ B.text <$ string "<nowiki>" <*> manyTillChar anyChar (try $ string "</nowiki>") nowiki = try $ B.text <$ string "<nowiki>" <*> manyTillChar anyChar (try $ string "</nowiki>")

View file

@ -61,7 +61,7 @@ import Text.Pandoc.Options (
import Text.Pandoc.Parsing hiding ((<|>)) import Text.Pandoc.Parsing hiding ((<|>))
import Text.Pandoc.Shared (addMetaField, blocksToInlines', crFilter, escapeURI, import Text.Pandoc.Shared (addMetaField, blocksToInlines', crFilter, escapeURI,
extractSpaces, htmlSpanLikeElements, elemText, splitTextBy, extractSpaces, htmlSpanLikeElements, elemText, splitTextBy,
onlySimpleTableCells, safeRead, underlineSpan, tshow) onlySimpleTableCells, safeRead, tshow)
import Text.Pandoc.Walk import Text.Pandoc.Walk
import Text.Parsec.Error import Text.Parsec.Error
import Text.TeXMath (readMathML, writeTeX) import Text.TeXMath (readMathML, writeTeX)
@ -749,7 +749,7 @@ pStrikeout =
return $ B.strikeout contents) return $ B.strikeout contents)
pUnderline :: PandocMonad m => TagParser m Inlines 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 :: PandocMonad m => TagParser m Inlines
pLineBreak = do pLineBreak = do

View file

@ -26,7 +26,7 @@ import Text.HTML.TagSoup.Entity (lookupEntity)
import Text.Pandoc.Builder import Text.Pandoc.Builder
import Text.Pandoc.Class.PandocMonad (PandocMonad) import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Options import Text.Pandoc.Options
import Text.Pandoc.Shared (underlineSpan, crFilter, safeRead) import Text.Pandoc.Shared (crFilter, safeRead)
import Text.TeXMath (readMathML, writeTeX) import Text.TeXMath (readMathML, writeTeX)
import Text.XML.Light import Text.XML.Light
import qualified Data.Set as S (fromList, member) import qualified Data.Set as S (fromList, member)
@ -456,7 +456,7 @@ parseInline (Elem e) =
"strike" -> strikeout <$> innerInlines "strike" -> strikeout <$> innerInlines
"sub" -> subscript <$> innerInlines "sub" -> subscript <$> innerInlines
"sup" -> superscript <$> innerInlines "sup" -> superscript <$> innerInlines
"underline" -> underlineSpan <$> innerInlines "underline" -> underline <$> innerInlines
"break" -> return linebreak "break" -> return linebreak
"sc" -> smallcaps <$> innerInlines "sc" -> smallcaps <$> innerInlines

View file

@ -909,7 +909,7 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList
, ("slash", lit "/") , ("slash", lit "/")
, ("textbf", extractSpaces strong <$> tok) , ("textbf", extractSpaces strong <$> tok)
, ("textnormal", extractSpaces (spanWith ("",["nodecor"],[])) <$> tok) , ("textnormal", extractSpaces (spanWith ("",["nodecor"],[])) <$> tok)
, ("underline", underlineSpan <$> tok) , ("underline", underline <$> tok)
, ("ldots", lit "") , ("ldots", lit "")
, ("vdots", lit "\8942") , ("vdots", lit "\8942")
, ("dots", lit "") , ("dots", lit "")
@ -1171,9 +1171,9 @@ inlineCommands = M.union inlineLanguageCommands $ M.fromList
-- include -- include
, ("input", rawInlineOr "input" $ include "input") , ("input", rawInlineOr "input" $ include "input")
-- soul package -- soul package
, ("ul", underlineSpan <$> tok) , ("ul", underline <$> tok)
-- ulem package -- ulem package
, ("uline", underlineSpan <$> tok) , ("uline", underline <$> tok)
-- plain tex stuff that should just be passed through as raw tex -- plain tex stuff that should just be passed through as raw tex
, ("ifdim", ifdim) , ("ifdim", ifdim)
] ]

View file

@ -1751,7 +1751,9 @@ bracketedSpan = try $ do
attr <- attributes attr <- attributes
return $ if isSmallCaps attr return $ if isSmallCaps attr
then B.smallcaps <$> lab 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 -- | We treat a span as SmallCaps if class is "smallcaps" (and
-- no other attributes are set or if style is "font-variant:small-caps" -- no other attributes are set or if style is "font-variant:small-caps"
@ -1765,6 +1767,13 @@ isSmallCaps ("",[],kvs) =
Nothing -> False Nothing -> False
isSmallCaps _ = 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 regLink :: PandocMonad m
=> (Attr -> Text -> Text -> Inlines -> Inlines) => (Attr -> Text -> Text -> Inlines -> Inlines)
-> F Inlines -> F Inlines
@ -1913,7 +1922,9 @@ spanHtml = try $ do
let keyvals = [(k,v) | (k,v) <- attrs, k /= "id" && k /= "class"] let keyvals = [(k,v) | (k,v) <- attrs, k /= "id" && k /= "class"]
return $ if isSmallCaps (ident, classes, keyvals) return $ if isSmallCaps (ident, classes, keyvals)
then B.smallcaps <$> contents 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 :: PandocMonad m => MarkdownParser m (F Blocks)
divHtml = try $ do divHtml = try $ do

View file

@ -29,7 +29,7 @@ import qualified Data.Set as Set
import Data.Maybe (fromMaybe, isNothing, maybeToList) import Data.Maybe (fromMaybe, isNothing, maybeToList)
import Data.Text (Text) import Data.Text (Text)
import qualified Data.Text as T 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 qualified Text.Pandoc.Builder as B
import Text.Pandoc.Class.PandocMonad (PandocMonad (..)) import Text.Pandoc.Class.PandocMonad (PandocMonad (..))
import Text.Pandoc.Definition import Text.Pandoc.Definition
@ -37,7 +37,7 @@ import Text.Pandoc.Error (PandocError (PandocParsecError))
import Text.Pandoc.Logging import Text.Pandoc.Logging
import Text.Pandoc.Options import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (F) 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. -- | Read Muse from an input string and return a Pandoc document.
readMuse :: PandocMonad m readMuse :: PandocMonad m
@ -849,7 +849,7 @@ emph = fmap B.emph <$> emphasisBetween (char '*' <* notFollowedBy (char '*'))
-- | Parse underline inline markup, indicated by @_@. -- | Parse underline inline markup, indicated by @_@.
-- Supported only in Emacs Muse mode, not Text::Amuse. -- Supported only in Emacs Muse mode, not Text::Amuse.
underlined :: PandocMonad m => MuseParser m (F Inlines) underlined :: PandocMonad m => MuseParser m (F Inlines)
underlined = fmap underlineSpan underlined = fmap underline
<$ guardDisabled Ext_amuse -- Supported only by Emacs Muse <$ guardDisabled Ext_amuse -- Supported only by Emacs Muse
<*> emphasisBetween (char '_') <*> emphasisBetween (char '_')

View file

@ -37,7 +37,7 @@ import Data.Semigroup (First(..), Option(..))
import Text.TeXMath (readMathML, writeTeX) import Text.TeXMath (readMathML, writeTeX)
import qualified Text.XML.Light as XML 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.MediaBag (MediaBag, insertMedia)
import Text.Pandoc.Shared import Text.Pandoc.Shared
import Text.Pandoc.Extensions (extensionsFromList, Extension(..)) import Text.Pandoc.Extensions (extensionsFromList, Extension(..))

View file

@ -27,7 +27,6 @@ import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Definition import Text.Pandoc.Definition
import Text.Pandoc.Options import Text.Pandoc.Options
import Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline) import Text.Pandoc.Readers.LaTeX (inlineCommand, rawLaTeXInline)
import Text.Pandoc.Shared (underlineSpan)
import Text.TeXMath (DisplayType (..), readTeX, writePandoc) import Text.TeXMath (DisplayType (..), readTeX, writePandoc)
import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap 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 '+' strikeout = fmap B.strikeout <$> emphasisBetween '+'
underline :: PandocMonad m => OrgParser m (F Inlines) underline :: PandocMonad m => OrgParser m (F Inlines)
underline = fmap underlineSpan <$> emphasisBetween '_' underline = fmap B.underline <$> emphasisBetween '_'
verbatim :: PandocMonad m => OrgParser m (F Inlines) verbatim :: PandocMonad m => OrgParser m (F Inlines)
verbatim = return . B.code <$> verbatimBetween '=' verbatim = return . B.code <$> verbatimBetween '='

View file

@ -52,7 +52,7 @@ import Text.Pandoc.Options
import Text.Pandoc.Parsing import Text.Pandoc.Parsing
import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isInlineTag) import Text.Pandoc.Readers.HTML (htmlTag, isBlockTag, isInlineTag)
import Text.Pandoc.Readers.LaTeX (rawLaTeXBlock, rawLaTeXInline) 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. -- | Parse a Textile text and return a Pandoc document.
readTextile :: PandocMonad m readTextile :: PandocMonad m
@ -451,7 +451,7 @@ inlineMarkup = choice [ simpleInline (string "??") (B.cite [])
, simpleInline (string "__") B.emph , simpleInline (string "__") B.emph
, simpleInline (char '*') B.strong , simpleInline (char '*') B.strong
, simpleInline (char '_') B.emph , simpleInline (char '_') B.emph
, simpleInline (char '+') underlineSpan , simpleInline (char '+') B.underline
, simpleInline (char '-' <* notFollowedBy (char '-')) B.strikeout , simpleInline (char '-' <* notFollowedBy (char '-')) B.strikeout
, simpleInline (char '^') B.superscript , simpleInline (char '^') B.superscript
, simpleInline (char '~') B.subscript , simpleInline (char '~') B.subscript

View file

@ -31,8 +31,7 @@ import Data.Time (defaultTimeLocale)
import Text.Pandoc.Definition import Text.Pandoc.Definition
import Text.Pandoc.Options import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (space, spaces, uri) import Text.Pandoc.Parsing hiding (space, spaces, uri)
import Text.Pandoc.Shared (compactify, compactifyDL, crFilter, escapeURI, import Text.Pandoc.Shared (compactify, compactifyDL, crFilter, escapeURI)
underlineSpan)
type T2T = ParserT Text ParserState (Reader T2TMeta) type T2T = ParserT Text ParserState (Reader T2TMeta)
@ -378,7 +377,7 @@ bold :: T2T Inlines
bold = inlineMarkup inline B.strong '*' B.str bold = inlineMarkup inline B.strong '*' B.str
underline :: T2T Inlines underline :: T2T Inlines
underline = inlineMarkup inline underlineSpan '_' B.str underline = inlineMarkup inline B.underline '_' B.str
strike :: T2T Inlines strike :: T2T Inlines
strike = inlineMarkup inline B.strikeout '-' B.str strike = inlineMarkup inline B.strikeout '-' B.str

View file

@ -750,11 +750,12 @@ eastAsianLineBreakFilter = bottomUp go
go xs go xs
= 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. -- This probably belongs in Builder.hs in pandoc-types.
-- Will be replaced once Underline is an element. -- Will be replaced once Underline is an element.
underlineSpan :: Inlines -> Inlines underlineSpan :: Inlines -> Inlines
underlineSpan = B.spanWith ("", ["underline"], []) underlineSpan = B.underline
-- | Set of HTML elements that are represented as Span with a class equal as -- | Set of HTML elements that are represented as Span with a class equal as
-- the element tag itself. -- the element tag itself.

View file

@ -433,6 +433,9 @@ inlineToAsciiDoc opts (Emph lst) = do
isIntraword <- gets intraword isIntraword <- gets intraword
let marker = if isIntraword then "__" else "_" let marker = if isIntraword then "__" else "_"
return $ marker <> contents <> marker return $ marker <> contents <> marker
inlineToAsciiDoc opts (Underline lst) = do
contents <- inlineListToAsciiDoc opts lst
return $ "+++" <> contents <> "+++"
inlineToAsciiDoc opts (Strong lst) = do inlineToAsciiDoc opts (Strong lst) = do
contents <- inlineListToAsciiDoc opts lst contents <- inlineListToAsciiDoc opts lst
isIntraword <- gets intraword isIntraword <- gets intraword

View file

@ -237,6 +237,11 @@ inlineToNodes opts SoftBreak
| writerWrapText opts == WrapNone = (node (TEXT " ") [] :) | writerWrapText opts == WrapNone = (node (TEXT " ") [] :)
| otherwise = (node SOFTBREAK [] :) | otherwise = (node SOFTBREAK [] :)
inlineToNodes opts (Emph xs) = (node EMPH (inlinesToNodes opts xs) :) 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 (Strong xs) = (node STRONG (inlinesToNodes opts xs) :)
inlineToNodes opts (Strikeout xs) inlineToNodes opts (Strikeout xs)
| isEnabled Ext_strikeout opts = (node (CUSTOM_INLINE "~~" "~~") (inlinesToNodes opts xs) :) | isEnabled Ext_strikeout opts = (node (CUSTOM_INLINE "~~" "~~") (inlinesToNodes opts xs) :)

View file

@ -368,6 +368,9 @@ inlineToConTeXt :: PandocMonad m
inlineToConTeXt (Emph lst) = do inlineToConTeXt (Emph lst) = do
contents <- inlineListToConTeXt lst contents <- inlineListToConTeXt lst
return $ braces $ "\\em " <> contents return $ braces $ "\\em " <> contents
inlineToConTeXt (Underline lst) = do
contents <- inlineListToConTeXt lst
return $ "\\underbar" <> braces contents
inlineToConTeXt (Strong lst) = do inlineToConTeXt (Strong lst) = do
contents <- inlineListToConTeXt lst contents <- inlineListToConTeXt lst
return $ braces $ "\\bf " <> contents return $ braces $ "\\bf " <> contents

View file

@ -186,6 +186,8 @@ inlineToCustom SoftBreak = Lua.callFunc "SoftBreak"
inlineToCustom (Emph lst) = Lua.callFunc "Emph" (Stringify lst) 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 (Strong lst) = Lua.callFunc "Strong" (Stringify lst)
inlineToCustom (Strikeout lst) = Lua.callFunc "Strikeout" (Stringify lst) inlineToCustom (Strikeout lst) = Lua.callFunc "Strikeout" (Stringify lst)

View file

@ -323,6 +323,8 @@ inlineToDocbook :: PandocMonad m => WriterOptions -> Inline -> DB m (Doc Text)
inlineToDocbook _ (Str str) = return $ literal $ escapeStringForXML str inlineToDocbook _ (Str str) = return $ literal $ escapeStringForXML str
inlineToDocbook opts (Emph lst) = inlineToDocbook opts (Emph lst) =
inTagsSimple "emphasis" <$> inlinesToDocbook opts lst inTagsSimple "emphasis" <$> inlinesToDocbook opts lst
inlineToDocbook opts (Underline lst) =
inTags False "emphasis" [("role", "underline")] <$> inlinesToDocbook opts lst
inlineToDocbook opts (Strong lst) = inlineToDocbook opts (Strong lst) =
inTags False "emphasis" [("role", "strong")] <$> inlinesToDocbook opts lst inTags False "emphasis" [("role", "strong")] <$> inlinesToDocbook opts lst
inlineToDocbook opts (Strikeout lst) = inlineToDocbook opts (Strikeout lst) =

View file

@ -1158,9 +1158,6 @@ inlineToOpenXML' _ (Str str) =
formattedString str formattedString str
inlineToOpenXML' opts Space = inlineToOpenXML opts (Str " ") inlineToOpenXML' opts Space = inlineToOpenXML opts (Str " ")
inlineToOpenXML' opts SoftBreak = 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 inlineToOpenXML' _ (Span (ident,["comment-start"],kvs) ils) = do
-- prefer the "id" in kvs, since that is the one produced by the docx -- prefer the "id" in kvs, since that is the one produced by the docx
-- reader. -- reader.
@ -1234,6 +1231,9 @@ inlineToOpenXML' opts (Strong lst) =
withTextProp (mknode "w:b" [] ()) $ inlinesToOpenXML opts lst withTextProp (mknode "w:b" [] ()) $ inlinesToOpenXML opts lst
inlineToOpenXML' opts (Emph lst) = inlineToOpenXML' opts (Emph lst) =
withTextProp (mknode "w:i" [] ()) $ inlinesToOpenXML opts 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) = inlineToOpenXML' opts (Subscript lst) =
withTextProp (mknode "w:vertAlign" [("w:val","subscript")] ()) withTextProp (mknode "w:vertAlign" [("w:val","subscript")] ())
$ inlinesToOpenXML opts lst $ inlinesToOpenXML opts lst

View file

@ -402,6 +402,10 @@ inlineToDokuWiki opts (Emph lst) = do
contents <- inlineListToDokuWiki opts lst contents <- inlineListToDokuWiki opts lst
return $ "//" <> contents <> "//" return $ "//" <> contents <> "//"
inlineToDokuWiki opts (Underline lst) = do
contents <- inlineListToDokuWiki opts lst
return $ "__" <> contents <> "__"
inlineToDokuWiki opts (Strong lst) = do inlineToDokuWiki opts (Strong lst) = do
contents <- inlineListToDokuWiki opts lst contents <- inlineListToDokuWiki opts lst
return $ "**" <> contents <> "**" return $ "**" <> contents <> "**"

View file

@ -406,6 +406,7 @@ toXml :: PandocMonad m => Inline -> FBM m [Content]
toXml (Str s) = return [txt s] toXml (Str s) = return [txt s]
toXml (Span _ ils) = cMapM toXml ils toXml (Span _ ils) = cMapM toXml ils
toXml (Emph ss) = list `liftM` wrap "emphasis" ss 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 (Strong ss) = list `liftM` wrap "strong" ss
toXml (Strikeout ss) = list `liftM` wrap "strikethrough" ss toXml (Strikeout ss) = list `liftM` wrap "strikethrough" ss
toXml (Superscript ss) = list `liftM` wrap "sup" ss toXml (Superscript ss) = list `liftM` wrap "sup" ss
@ -529,6 +530,7 @@ list = (:[])
plain :: Inline -> String plain :: Inline -> String
plain (Str s) = T.unpack s plain (Str s) = T.unpack s
plain (Emph ss) = cMap plain ss plain (Emph ss) = cMap plain ss
plain (Underline ss) = cMap plain ss
plain (Span _ ss) = cMap plain ss plain (Span _ ss) = cMap plain ss
plain (Strong ss) = cMap plain ss plain (Strong ss) = cMap plain ss
plain (Strikeout ss) = cMap plain ss plain (Strikeout ss) = cMap plain ss

View file

@ -1049,6 +1049,7 @@ inlineToHtml opts inline = do
] ]
(Emph lst) -> H.em <$> inlineListToHtml opts lst (Emph lst) -> H.em <$> inlineListToHtml opts lst
(Underline lst) -> H.u <$> inlineListToHtml opts lst
(Strong lst) -> H.strong <$> inlineListToHtml opts lst (Strong lst) -> H.strong <$> inlineListToHtml opts lst
(Code attr@(ids,cs,kvs) str) (Code attr@(ids,cs,kvs) str)
-> case hlCode of -> case hlCode of

View file

@ -209,6 +209,9 @@ inlineToHaddock opts (Span (ident,_,_) ils) = do
inlineToHaddock opts (Emph lst) = do inlineToHaddock opts (Emph lst) = do
contents <- inlineListToHaddock opts lst contents <- inlineListToHaddock opts lst
return $ "/" <> contents <> "/" return $ "/" <> contents <> "/"
-- Underline is not supported, treat the same as Emph
inlineToHaddock opts (Underline lst) =
inlineToHaddock opts (Emph lst)
inlineToHaddock opts (Strong lst) = do inlineToHaddock opts (Strong lst) = do
contents <- inlineListToHaddock opts lst contents <- inlineListToHaddock opts lst
return $ "__" <> contents <> "__" return $ "__" <> contents <> "__"

View file

@ -60,6 +60,7 @@ defaultWriterState = WriterState{
-- inline names (appear in InDesign's character styles pane) -- inline names (appear in InDesign's character styles pane)
emphName :: Text emphName :: Text
underlineName :: Text
strongName :: Text strongName :: Text
strikeoutName :: Text strikeoutName :: Text
superscriptName :: Text superscriptName :: Text
@ -68,6 +69,7 @@ smallCapsName :: Text
codeName :: Text codeName :: Text
linkName :: Text linkName :: Text
emphName = "Italic" emphName = "Italic"
underlineName = "Underline"
strongName = "Bold" strongName = "Bold"
strikeoutName = "Strikeout" strikeoutName = "Strikeout"
superscriptName = "Superscript" 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 :: PandocMonad m => WriterOptions -> Style -> Inline -> WS m (Doc Text)
inlineToICML _ style (Str str) = charStyle style $ literal $ escapeStringForXML str inlineToICML _ style (Str str) = charStyle style $ literal $ escapeStringForXML str
inlineToICML opts style (Emph lst) = inlinesToICML opts (emphName:style) lst 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 (Strong lst) = inlinesToICML opts (strongName:style) lst
inlineToICML opts style (Strikeout lst) = inlinesToICML opts (strikeoutName:style) lst inlineToICML opts style (Strikeout lst) = inlinesToICML opts (strikeoutName:style) lst
inlineToICML opts style (Superscript lst) = inlinesToICML opts (superscriptName:style) lst inlineToICML opts style (Superscript lst) = inlinesToICML opts (superscriptName:style) lst

View file

@ -424,6 +424,8 @@ inlineToJATS :: PandocMonad m => WriterOptions -> Inline -> JATS m (Doc Text)
inlineToJATS _ (Str str) = return $ text $ T.unpack $ escapeStringForXML str inlineToJATS _ (Str str) = return $ text $ T.unpack $ escapeStringForXML str
inlineToJATS opts (Emph lst) = inlineToJATS opts (Emph lst) =
inTagsSimple "italic" <$> inlinesToJATS opts lst inTagsSimple "italic" <$> inlinesToJATS opts lst
inlineToJATS opts (Underline lst) =
inTagsSimple "underline" <$> inlinesToJATS opts lst
inlineToJATS opts (Strong lst) = inlineToJATS opts (Strong lst) =
inTagsSimple "bold" <$> inlinesToJATS opts lst inTagsSimple "bold" <$> inlinesToJATS opts lst
inlineToJATS opts (Strikeout lst) = inlineToJATS opts (Strikeout lst) =

View file

@ -193,6 +193,7 @@ toJiraInlines inlines = do
Code _ cs -> return . singleton $ Code _ cs -> return . singleton $
Jira.Monospaced (escapeSpecialChars cs) Jira.Monospaced (escapeSpecialChars cs)
Emph xs -> styled Jira.Emphasis xs Emph xs -> styled Jira.Emphasis xs
Underline xs -> styled Jira.Insert xs
Image attr _ tgt -> imageToJira attr (fst tgt) (snd tgt) Image attr _ tgt -> imageToJira attr (fst tgt) (snd tgt)
LineBreak -> pure . singleton $ Jira.Linebreak LineBreak -> pure . singleton $ Jira.Linebreak
Link attr xs tgt -> toJiraLink attr tgt xs Link attr xs tgt -> toJiraLink attr tgt xs

View file

@ -1140,6 +1140,7 @@ inlineToLaTeX (Span (id',classes,kvs) ils) = do
then braces contents then braces contents
else foldr inCmd contents cmds) else foldr inCmd contents cmds)
inlineToLaTeX (Emph lst) = inCmd "emph" <$> inlineListToLaTeX lst inlineToLaTeX (Emph lst) = inCmd "emph" <$> inlineListToLaTeX lst
inlineToLaTeX (Underline lst) = inCmd "underline" <$> inlineListToLaTeX lst
inlineToLaTeX (Strong lst) = inCmd "textbf" <$> inlineListToLaTeX lst inlineToLaTeX (Strong lst) = inCmd "textbf" <$> inlineListToLaTeX lst
inlineToLaTeX (Strikeout lst) = do inlineToLaTeX (Strikeout lst) = do
-- we need to protect VERB in an mbox or we get an error -- we need to protect VERB in an mbox or we get an error

View file

@ -270,6 +270,9 @@ inlineToMan :: PandocMonad m => WriterOptions -> Inline -> StateT WriterState m
inlineToMan opts (Span _ ils) = inlineListToMan opts ils inlineToMan opts (Span _ ils) = inlineListToMan opts ils
inlineToMan opts (Emph lst) = inlineToMan opts (Emph lst) =
withFontFeature 'I' (inlineListToMan opts 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) = inlineToMan opts (Strong lst) =
withFontFeature 'B' (inlineListToMan opts lst) withFontFeature 'B' (inlineListToMan opts lst)
inlineToMan opts (Strikeout lst) = do inlineToMan opts (Strikeout lst) = do

View file

@ -1045,6 +1045,21 @@ inlineToMarkdown opts (Emph lst) = do
then "_" <> contents <> "_" then "_" <> contents <> "_"
else contents else 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 _ (Strong []) = return empty
inlineToMarkdown opts (Strong lst) = do inlineToMarkdown opts (Strong lst) = do
plain <- asks envPlain plain <- asks envPlain

View file

@ -372,6 +372,10 @@ inlineToMediaWiki (Emph lst) = do
contents <- inlineListToMediaWiki lst contents <- inlineListToMediaWiki lst
return $ "''" <> contents <> "''" return $ "''" <> contents <> "''"
inlineToMediaWiki (Underline lst) = do
contents <- inlineListToMediaWiki lst
return $ "<u>" <> contents <> "</u>"
inlineToMediaWiki (Strong lst) = do inlineToMediaWiki (Strong lst) = do
contents <- inlineListToMediaWiki lst contents <- inlineListToMediaWiki lst
return $ "'''" <> contents <> "'''" return $ "'''" <> contents <> "'''"

View file

@ -351,6 +351,8 @@ inlineToMs :: PandocMonad m => WriterOptions -> Inline -> MS m (Doc Text)
inlineToMs opts (Span _ ils) = inlineListToMs opts ils inlineToMs opts (Span _ ils) = inlineListToMs opts ils
inlineToMs opts (Emph lst) = inlineToMs opts (Emph lst) =
withFontFeature 'I' (inlineListToMs opts lst) withFontFeature 'I' (inlineListToMs opts lst)
inlineToMs opts (Underline lst) =
inlineToMs opts (Emph lst)
inlineToMs opts (Strong lst) = inlineToMs opts (Strong lst) =
withFontFeature 'B' (inlineListToMs opts lst) withFontFeature 'B' (inlineListToMs opts lst)
inlineToMs opts (Strikeout lst) = do inlineToMs opts (Strikeout lst) = do

View file

@ -594,6 +594,13 @@ inlineToMuse (Strong [Emph lst]) = do
else if null lst' || startsWithSpace lst' || endsWithSpace lst' else if null lst' || startsWithSpace lst' || endsWithSpace lst'
then emphasis "**<em>" "</em>**" lst' then emphasis "**<em>" "</em>**" lst'
else emphasis "***" "***" 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 inlineToMuse (Strong lst) = do
useTags <- gets stUseTags useTags <- gets stUseTags
let lst' = normalizeInlineList lst let lst' = normalizeInlineList lst

View file

@ -512,6 +512,7 @@ inlineToOpenDocument o ils
LineBreak -> return $ selfClosingTag "text:line-break" [] LineBreak -> return $ selfClosingTag "text:line-break" []
Str s -> return $ handleSpaces $ escapeStringForXML s Str s -> return $ handleSpaces $ escapeStringForXML s
Emph l -> withTextStyle Italic $ inlinesToOpenDocument o l Emph l -> withTextStyle Italic $ inlinesToOpenDocument o l
Underline l -> withTextStyle Under $ inlinesToOpenDocument o l
Strong l -> withTextStyle Bold $ inlinesToOpenDocument o l Strong l -> withTextStyle Bold $ inlinesToOpenDocument o l
Strikeout l -> withTextStyle Strike $ inlinesToOpenDocument o l Strikeout l -> withTextStyle Strike $ inlinesToOpenDocument o l
Superscript l -> withTextStyle Sup $ inlinesToOpenDocument o l Superscript l -> withTextStyle Sup $ inlinesToOpenDocument o l
@ -692,6 +693,7 @@ paraTableStyles t s (a:xs)
data TextStyle = Italic data TextStyle = Italic
| Bold | Bold
| Under
| Strike | Strike
| Sub | Sub
| Sup | Sup
@ -710,6 +712,9 @@ textStyleAttr m s
| Bold <- s = Map.insert "fo:font-weight" "bold" . | Bold <- s = Map.insert "fo:font-weight" "bold" .
Map.insert "style:font-weight-asian" "bold" . Map.insert "style:font-weight-asian" "bold" .
Map.insert "style:font-weight-complex" "bold" $ m 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 | Strike <- s = Map.insert "style:text-line-through-style" "solid" m
| Sub <- s = Map.insert "style:text-position" "sub 58%" m | Sub <- s = Map.insert "style:text-position" "sub 58%" m
| Sup <- s = Map.insert "style:text-position" "super 58%" m | Sup <- s = Map.insert "style:text-position" "super 58%" m

View file

@ -329,6 +329,9 @@ inlineToOrg (Span _ lst) =
inlineToOrg (Emph lst) = do inlineToOrg (Emph lst) = do
contents <- inlineListToOrg lst contents <- inlineListToOrg lst
return $ "/" <> contents <> "/" return $ "/" <> contents <> "/"
inlineToOrg (Underline lst) = do
contents <- inlineListToOrg lst
return $ "_" <> contents <> "_"
inlineToOrg (Strong lst) = do inlineToOrg (Strong lst) = do
contents <- inlineListToOrg lst contents <- inlineListToOrg lst
return $ "*" <> contents <> "*" return $ "*" <> contents <> "*"

View file

@ -323,6 +323,9 @@ inlineToParElems (Str s) = do
inlineToParElems (Emph ils) = inlineToParElems (Emph ils) =
local (\r -> r{envRunProps = (envRunProps r){rPropItalics=True}}) $ local (\r -> r{envRunProps = (envRunProps r){rPropItalics=True}}) $
inlinesToParElems ils inlinesToParElems ils
inlineToParElems (Underline ils) =
local (\r -> r{envRunProps = (envRunProps r){rPropUnderline=True}}) $
inlinesToParElems ils
inlineToParElems (Strong ils) = inlineToParElems (Strong ils) =
local (\r -> r{envRunProps = (envRunProps r){rPropBold=True}}) $ local (\r -> r{envRunProps = (envRunProps r){rPropBold=True}}) $
inlinesToParElems ils inlinesToParElems ils

View file

@ -415,6 +415,7 @@ transformInlines = insertBS .
hasContents :: Inline -> Bool hasContents :: Inline -> Bool
hasContents (Str "") = False hasContents (Str "") = False
hasContents (Emph []) = False hasContents (Emph []) = False
hasContents (Underline []) = False
hasContents (Strong []) = False hasContents (Strong []) = False
hasContents (Strikeout []) = False hasContents (Strikeout []) = False
hasContents (Superscript []) = False hasContents (Superscript []) = False
@ -474,6 +475,7 @@ transformInlines = insertBS .
okBeforeComplex _ = False okBeforeComplex _ = False
isComplex :: Inline -> Bool isComplex :: Inline -> Bool
isComplex (Emph _) = True isComplex (Emph _) = True
isComplex (Underline _) = True
isComplex (Strong _) = True isComplex (Strong _) = True
isComplex (SmallCaps _) = True isComplex (SmallCaps _) = True
isComplex (Strikeout _) = True isComplex (Strikeout _) = True
@ -538,6 +540,7 @@ mapNested f i = setInlineChildren i (f (dropInlineParent i))
dropInlineParent :: Inline -> [Inline] dropInlineParent :: Inline -> [Inline]
dropInlineParent (Link _ i _) = i dropInlineParent (Link _ i _) = i
dropInlineParent (Emph i) = i dropInlineParent (Emph i) = i
dropInlineParent (Underline i) = i
dropInlineParent (Strong i) = i dropInlineParent (Strong i) = i
dropInlineParent (Strikeout i) = i dropInlineParent (Strikeout i) = i
dropInlineParent (Superscript 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 :: Inline -> [Inline] -> Inline
setInlineChildren (Link a _ t) i = Link a i t setInlineChildren (Link a _ t) i = Link a i t
setInlineChildren (Emph _) i = Emph i setInlineChildren (Emph _) i = Emph i
setInlineChildren (Underline _) i = Underline i
setInlineChildren (Strong _) i = Strong i setInlineChildren (Strong _) i = Strong i
setInlineChildren (Strikeout _) i = Strikeout i setInlineChildren (Strikeout _) i = Strikeout i
setInlineChildren (Superscript _) i = Superscript i setInlineChildren (Superscript _) i = Superscript i
@ -582,6 +586,9 @@ inlineToRST (Span (_,_,kvs) ils) = do
inlineToRST (Emph lst) = do inlineToRST (Emph lst) = do
contents <- writeInlines lst contents <- writeInlines lst
return $ "*" <> contents <> "*" return $ "*" <> contents <> "*"
-- Underline is not supported, fall back to Emph
inlineToRST (Underline lst) =
inlineToRST (Emph lst)
inlineToRST (Strong lst) = do inlineToRST (Strong lst) = do
contents <- writeInlines lst contents <- writeInlines lst
return $ "**" <> contents <> "**" return $ "**" <> contents <> "**"

View file

@ -351,6 +351,9 @@ inlineToRTF (Span _ lst) = inlinesToRTF lst
inlineToRTF (Emph lst) = do inlineToRTF (Emph lst) = do
contents <- inlinesToRTF lst contents <- inlinesToRTF lst
return $ "{\\i " <> contents <> "}" return $ "{\\i " <> contents <> "}"
inlineToRTF (Underline lst) = do
contents <- inlinesToRTF lst
return $ "{\\pnul " <> contents <> "}"
inlineToRTF (Strong lst) = do inlineToRTF (Strong lst) = do
contents <- inlinesToRTF lst contents <- inlinesToRTF lst
return $ "{\\b " <> contents <> "}" return $ "{\\b " <> contents <> "}"

View file

@ -231,6 +231,8 @@ inlineToTEI :: PandocMonad m => WriterOptions -> Inline -> m (Doc Text)
inlineToTEI _ (Str str) = return $ literal $ escapeStringForXML str inlineToTEI _ (Str str) = return $ literal $ escapeStringForXML str
inlineToTEI opts (Emph lst) = inlineToTEI opts (Emph lst) =
inTags False "hi" [("rendition","simple:italic")] <$> inlinesToTEI opts 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) = inlineToTEI opts (Strong lst) =
inTags False "hi" [("rendition", "simple:bold")] <$> inlinesToTEI opts lst inTags False "hi" [("rendition", "simple:bold")] <$> inlinesToTEI opts lst
inlineToTEI opts (Strikeout lst) = inlineToTEI opts (Strikeout lst) =

View file

@ -392,6 +392,10 @@ inlineToTexinfo (Span _ lst) =
inlineToTexinfo (Emph lst) = inlineToTexinfo (Emph lst) =
inCmd "emph" <$> inlineListToTexinfo lst inCmd "emph" <$> inlineListToTexinfo lst
-- Underline isn't supported, fall back to Emph
inlineToTexinfo (Underline lst) =
inlineToTexinfo (Emph lst)
inlineToTexinfo (Strong lst) = inlineToTexinfo (Strong lst) =
inCmd "strong" <$> inlineListToTexinfo lst inCmd "strong" <$> inlineListToTexinfo lst

View file

@ -386,6 +386,12 @@ inlineToTextile opts (Emph lst) = do
then "<em>" <> contents <> "</em>" then "<em>" <> contents <> "</em>"
else "_" <> contents <> "_" 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 inlineToTextile opts (Strong lst) = do
contents <- inlineListToTextile opts lst contents <- inlineListToTextile opts lst
return $ if '*' `elemText` contents return $ if '*' `elemText` contents

View file

@ -163,6 +163,10 @@ inlineToXWiki (Emph lst) = do
contents <- inlineListToXWiki lst contents <- inlineListToXWiki lst
return $ "//" <> contents <> "//" return $ "//" <> contents <> "//"
inlineToXWiki (Underline lst) = do
contents <- inlineListToXWiki lst
return $ "__" <> contents <> "__"
inlineToXWiki (Strong lst) = do inlineToXWiki (Strong lst) = do
contents <- inlineListToXWiki lst contents <- inlineListToXWiki lst
return $ "**" <> contents <> "**" return $ "**" <> contents <> "**"

View file

@ -273,6 +273,10 @@ inlineToZimWiki opts (Emph lst) = do
contents <- inlineListToZimWiki opts lst contents <- inlineListToZimWiki opts lst
return $ "//" <> contents <> "//" return $ "//" <> contents <> "//"
inlineToZimWiki opts (Underline lst) = do
contents <- inlineListToZimWiki opts lst
return $ "__" <> contents <> "__"
inlineToZimWiki opts (Strong lst) = do inlineToZimWiki opts (Strong lst) = do
contents <- inlineListToZimWiki opts lst contents <- inlineListToZimWiki opts lst
return $ "**" <> contents <> "**" return $ "**" <> contents <> "**"

View file

@ -22,7 +22,6 @@ import Tests.Helpers
import Text.Pandoc import Text.Pandoc
import Text.Pandoc.Arbitrary () import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder import Text.Pandoc.Builder
import Text.Pandoc.Shared (underlineSpan)
dokuwiki :: Text -> Pandoc dokuwiki :: Text -> Pandoc
dokuwiki = purely $ readDokuWiki def{ readerStandalone = True } dokuwiki = purely $ readDokuWiki def{ readerStandalone = True }
@ -42,7 +41,7 @@ tests = [ testGroup "inlines"
para (emph "italic") para (emph "italic")
, "Underlined" =: , "Underlined" =:
"__underlined__" =?> "__underlined__" =?>
para (underlineSpan "underlined") para (underline "underlined")
, "Monospaced" =: , "Monospaced" =:
"''monospaced''" =?> "''monospaced''" =?>
para (code "monospaced") para (code "monospaced")
@ -51,7 +50,7 @@ tests = [ testGroup "inlines"
para (code "monospaced") para (code "monospaced")
, "Combined" =: , "Combined" =:
"**__//''combine''//__**" =?> "**__//''combine''//__**" =?>
para (strong $ underlineSpan $ emph $ code "combine") para (strong $ underline $ emph $ code "combine")
, "Nowiki" =: , "Nowiki" =:
T.unlines [ "<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." , "This is some text which contains addresses like this: http://www.splitbrain.org and **formatting**, but nothing is done with it."

View file

@ -25,7 +25,6 @@ import Tests.Helpers
import Text.Pandoc import Text.Pandoc
import Text.Pandoc.Arbitrary () import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder import Text.Pandoc.Builder
import Text.Pandoc.Shared (underlineSpan)
import Text.Pandoc.Writers.Shared (toLegacyTable) import Text.Pandoc.Writers.Shared (toLegacyTable)
import Text.Pandoc.Walk import Text.Pandoc.Walk
@ -209,7 +208,7 @@ tests =
para (strong . emph $ "foo******bar") para (strong . emph $ "foo******bar")
, test emacsMuse "Underline" , test emacsMuse "Underline"
("_Underline_" =?> para (underlineSpan "Underline")) ("_Underline_" =?> para (underline "Underline"))
, "Superscript tag" =: "<sup>Superscript</sup>" =?> para (superscript "Superscript") , "Superscript tag" =: "<sup>Superscript</sup>" =?> para (superscript "Superscript")

View file

@ -19,7 +19,6 @@ import Test.Tasty (TestTree, testGroup)
import Tests.Helpers ((=?>)) import Tests.Helpers ((=?>))
import Tests.Readers.Org.Shared ((=:), spcSep) import Tests.Readers.Org.Shared ((=:), spcSep)
import Text.Pandoc.Builder import Text.Pandoc.Builder
import Text.Pandoc.Shared (underlineSpan)
import qualified Data.Text as T import qualified Data.Text as T
import qualified Tests.Readers.Org.Inline.Citation as Citation import qualified Tests.Readers.Org.Inline.Citation as Citation
import qualified Tests.Readers.Org.Inline.Note as Note import qualified Tests.Readers.Org.Inline.Note as Note
@ -49,7 +48,7 @@ tests =
, "Underline" =: , "Underline" =:
"_underline_" =?> "_underline_" =?>
para (underlineSpan "underline") para (underline "underline")
, "Strikeout" =: , "Strikeout" =:
"+Kill Bill+" =?> "+Kill Bill+" =?>

View file

@ -23,7 +23,6 @@ import Tests.Helpers
import Text.Pandoc import Text.Pandoc
import Text.Pandoc.Arbitrary () import Text.Pandoc.Arbitrary ()
import Text.Pandoc.Builder import Text.Pandoc.Builder
import Text.Pandoc.Shared (underlineSpan)
t2t :: Text -> Pandoc t2t :: Text -> Pandoc
-- t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def -- t2t = handleError . readTxt2Tags (T2TMeta "date" "mtime" "in" "out") def
@ -94,12 +93,12 @@ tests =
, "Inline markup is greedy" =: , "Inline markup is greedy" =:
"***** ///// _____ ----- ````` \"\"\"\"\" '''''" =?> "***** ///// _____ ----- ````` \"\"\"\"\" '''''" =?>
para (spcSep [strong "*", emph "/", underlineSpan "_" para (spcSep [strong "*", emph "/", underline "_"
, strikeout "-", code "`", text "\"" , strikeout "-", code "`", text "\""
, rawInline "html" "'"]) , rawInline "html" "'"])
, "Markup must be greedy" =: , "Markup must be greedy" =:
"********** ////////// __________ ---------- `````````` \"\"\"\"\"\"\"\"\"\" ''''''''''" =?> "********** ////////// __________ ---------- `````````` \"\"\"\"\"\"\"\"\"\" ''''''''''" =?>
para (spcSep [strong "******", emph "//////", underlineSpan "______" para (spcSep [strong "******", emph "//////", underline "______"
, strikeout "------", code "``````", text "\"\"\"\"\"\"" , strikeout "------", code "``````", text "\"\"\"\"\"\""
, rawInline "html" "''''''"]) , rawInline "html" "''''''"])
, "Inlines must be glued" =: , "Inlines must be glued" =:

View file

@ -1,2 +1,3 @@
Pandoc (Meta {unMeta = fromList []})
[Header 1 ("test",[],[]) [Str "Test"] [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 "."]]

View file

@ -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 "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 "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 "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."]] ,Para [Str "A",Space,Str "line",LineBreak,Str "break."]]

View file

@ -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 "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,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 "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 "."] ,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 ,HorizontalRule
,Header 1 ("smart-quotes-ellipses-dashes",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"] ,Header 1 ("smart-quotes-ellipses-dashes",[],[]) [Str "Smart",Space,Str "quotes,",Space,Str "ellipses,",Space,Str "dashes"]

View file

@ -86,7 +86,7 @@ Pandoc (Meta {unMeta = fromList []})
,([Str "beer"], ,([Str "beer"],
[[Plain [Str "fresh",Space,Str "and",Space,Str "bitter"]]])] [[Plain [Str "fresh",Space,Str "and",Space,Str "bitter"]]])]
,Header 1 ("inline-markup",[],[]) [Str "Inline",Space,Str "Markup"] ,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 [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 "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."] ,Para [Str "Dashes",Space,Str ":",Space,Str "How",Space,Str "cool",Space,Str "\8212",Space,Str "automatic",Space,Str "dashes."]

View file

@ -29,8 +29,8 @@ Pandoc (Meta {unMeta = fromList [("author",MetaList [MetaInlines [Str "author"]]
,Para [Strikeout [Str "-------+--------"]] ,Para [Strikeout [Str "-------+--------"]]
,Para [Str "(",Space,Strikeout [Str "----------------"],Space,Str ")"] ,Para [Str "(",Space,Strikeout [Str "----------------"],Space,Str ")"]
,Header 1 ("inline",[],[]) [Str "Inline"] ,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 "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,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 "*"],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 "////",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 "''"] ,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"] ,Header 1 ("link",[],[]) [Str "Link"]