From 7f8a3c6cb70e61666598873dbcea8ef45ab85b56 Mon Sep 17 00:00:00 2001
From: hftf <hftf@users.noreply.github.com>
Date: Fri, 27 Oct 2017 18:45:00 -0400
Subject: Consistent underline for Readers (#2270)

* Added underlineSpan builder function.  This can be easily updated if needed. The purpose is for Readers to transform underlines consistently.

* Docx Reader: Use underlineSpan and update test

* Org Reader: Use underlineSpan and add test

* Textile Reader: Use underlineSpan and add test case

* Txt2Tags Reader: Use underlineSpan and update test

* HTML Reader: Use underlineSpan and add test case
---
 src/Text/Pandoc/Readers/Docx.hs        | 5 +++--
 src/Text/Pandoc/Readers/HTML.hs        | 6 +++++-
 src/Text/Pandoc/Readers/Org/Inlines.hs | 4 ++--
 src/Text/Pandoc/Readers/Textile.hs     | 4 ++--
 src/Text/Pandoc/Readers/Txt2Tags.hs    | 4 ++--
 src/Text/Pandoc/Shared.hs              | 8 ++++++++
 6 files changed, 22 insertions(+), 9 deletions(-)

(limited to 'src')

diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs
index 21aa358f2..2448d24e5 100644
--- a/src/Text/Pandoc/Readers/Docx.hs
+++ b/src/Text/Pandoc/Readers/Docx.hs
@@ -52,12 +52,13 @@ implemented, [-] means partially implemented):
 * Inlines
 
   - [X] Str
-  - [X] Emph (italics and underline both read as Emph)
+  - [X] Emph
   - [X] Strong
   - [X] Strikeout
   - [X] Superscript
   - [X] Subscript
   - [X] SmallCaps
+  - [-] Underline (was previously converted to Emph)
   - [ ] Quoted
   - [ ] Cite
   - [X] Code (styled with `VerbatimChar`)
@@ -287,7 +288,7 @@ runStyleToTransform rPr
   | Just SubScrpt <- rVertAlign rPr =
       subscript . (runStyleToTransform rPr {rVertAlign = Nothing})
   | Just "single" <- rUnderline rPr =
-      emph . (runStyleToTransform rPr {rUnderline = Nothing})
+      underlineSpan . (runStyleToTransform rPr {rUnderline = Nothing})
   | otherwise = id
 
 runToInlines :: PandocMonad m => Run -> DocxContext m Inlines
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index c648c8628..277405b09 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -45,7 +45,7 @@ import Text.Pandoc.Definition
 import qualified Text.Pandoc.Builder as B
 import Text.Pandoc.Builder (Blocks, Inlines, trimInlines, HasMeta(..))
 import Text.Pandoc.Shared ( extractSpaces, addMetaField
-                          , escapeURI, safeRead, crFilter )
+                          , escapeURI, safeRead, crFilter, underlineSpan )
 import Text.Pandoc.Options (
          ReaderOptions(readerExtensions,readerStripComments), extensionEnabled,
          Extension (Ext_epub_html_exts,
@@ -627,6 +627,7 @@ inline = choice
            , pSuperscript
            , pSubscript
            , pStrikeout
+           , pUnderline
            , pLineBreak
            , pLink
            , pImage
@@ -696,6 +697,9 @@ pStrikeout = do
             contents <- mconcat <$> manyTill inline (pCloses "span")
             return $ B.strikeout contents)
 
+pUnderline :: PandocMonad m => TagParser m Inlines
+pUnderline = pInlinesInTags "u" underlineSpan <|> pInlinesInTags "ins" underlineSpan
+
 pLineBreak :: PandocMonad m => TagParser m Inlines
 pLineBreak = do
   pSelfClosing (=="br") (const True)
diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs
index 39f4dc926..f3649af66 100644
--- a/src/Text/Pandoc/Readers/Org/Inlines.hs
+++ b/src/Text/Pandoc/Readers/Org/Inlines.hs
@@ -45,6 +45,7 @@ import Text.Pandoc.Class (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
 
@@ -572,9 +573,8 @@ strong    = fmap B.strong       <$> emphasisBetween '*'
 strikeout :: PandocMonad m => OrgParser m (F Inlines)
 strikeout = fmap B.strikeout    <$> emphasisBetween '+'
 
--- There is no underline, so we use strong instead.
 underline :: PandocMonad m => OrgParser m (F Inlines)
-underline = fmap B.strong       <$> emphasisBetween '_'
+underline = fmap underlineSpan  <$> emphasisBetween '_'
 
 verbatim  :: PandocMonad m => OrgParser m (F Inlines)
 verbatim  = return . B.code     <$> verbatimBetween '='
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 9cd3d2c36..90567ef23 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -68,7 +68,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 (trim, crFilter)
+import Text.Pandoc.Shared (trim, crFilter, underlineSpan)
 import Data.Text (Text)
 import qualified Data.Text as T
 
@@ -468,7 +468,7 @@ inlineMarkup = choice [ simpleInline (string "??") (B.cite [])
                       , simpleInline (string "__") B.emph
                       , simpleInline (char '*') B.strong
                       , simpleInline (char '_') B.emph
-                      , simpleInline (char '+') B.emph  -- approximates underline
+                      , simpleInline (char '+') underlineSpan
                       , simpleInline (char '-' <* notFollowedBy (char '-')) B.strikeout
                       , simpleInline (char '^') B.superscript
                       , simpleInline (char '~') B.subscript
diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs
index 2d3e541cf..0e68cdfb7 100644
--- a/src/Text/Pandoc/Readers/Txt2Tags.hs
+++ b/src/Text/Pandoc/Readers/Txt2Tags.hs
@@ -41,7 +41,7 @@ import qualified Text.Pandoc.Builder as B
 import Text.Pandoc.Definition
 import Text.Pandoc.Options
 import Text.Pandoc.Parsing hiding (space, spaces, uri)
-import Text.Pandoc.Shared (compactify, compactifyDL, escapeURI, crFilter)
+import Text.Pandoc.Shared (compactify, compactifyDL, escapeURI, crFilter, underlineSpan)
 import Control.Monad (guard, void, when)
 import Control.Monad.Reader (Reader, asks, runReader)
 import Data.Default
@@ -393,7 +393,7 @@ bold :: T2T Inlines
 bold = inlineMarkup inline B.strong '*' (B.str)
 
 underline :: T2T Inlines
-underline = inlineMarkup inline B.emph '_' (B.str)
+underline = inlineMarkup inline underlineSpan '_' (B.str)
 
 strike :: T2T Inlines
 strike = inlineMarkup inline B.strikeout '-' (B.str)
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs
index 4c5f464d8..2307470a1 100644
--- a/src/Text/Pandoc/Shared.hs
+++ b/src/Text/Pandoc/Shared.hs
@@ -72,6 +72,7 @@ module Text.Pandoc.Shared (
                      addMetaField,
                      makeMeta,
                      eastAsianLineBreakFilter,
+                     underlineSpan,
                      -- * TagSoup HTML handling
                      renderTags',
                      -- * File handling
@@ -563,6 +564,13 @@ eastAsianLineBreakFilter = bottomUp go
                _ -> x:SoftBreak:y:zs
         go xs = xs
 
+-- | Builder for underline.
+-- This probably belongs in Builder.hs in pandoc-types.
+-- Will be replaced once Underline is an element.
+underlineSpan :: Inlines -> Inlines
+underlineSpan = B.spanWith ("", ["underline"], [])
+
+
 --
 -- TagSoup HTML handling
 --
-- 
cgit v1.2.3