aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/HTML.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/HTML.hs')
-rw-r--r--src/Text/Pandoc/Readers/HTML.hs17
1 files changed, 10 insertions, 7 deletions
diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs
index e8dd9ec11..0e79f9ec3 100644
--- a/src/Text/Pandoc/Readers/HTML.hs
+++ b/src/Text/Pandoc/Readers/HTML.hs
@@ -43,14 +43,14 @@ module Text.Pandoc.Readers.HTML ( readHtml
) where
import Control.Applicative ((<|>))
-import Control.Arrow ((***))
+import Control.Arrow (first)
import Control.Monad (guard, mplus, msum, mzero, unless, void)
import Control.Monad.Except (throwError)
import Control.Monad.Reader (ReaderT, ask, asks, lift, local, runReaderT)
import Data.Char (isAlphaNum, isDigit, isLetter)
import Data.Default (Default (..), def)
import Data.Foldable (for_)
-import Data.List (intercalate, isPrefixOf)
+import Data.List (isPrefixOf)
import Data.List.Split (wordsBy, splitWhen)
import qualified Data.Map as M
import Data.Maybe (fromMaybe, isJust, isNothing)
@@ -531,15 +531,18 @@ pCol = try $ do
skipMany pBlank
optional $ pSatisfy (matchTagClose "col")
skipMany pBlank
- return $ case lookup "width" attribs of
+ let width = case lookup "width" attribs of
Nothing -> case lookup "style" attribs of
Just ('w':'i':'d':'t':'h':':':xs) | '%' `elem` xs ->
- fromMaybe 0.0 $ safeRead ('0':'.':filter
+ fromMaybe 0.0 $ safeRead (filter
(`notElem` (" \t\r\n%'\";" :: [Char])) xs)
_ -> 0.0
Just x | not (null x) && last x == '%' ->
- fromMaybe 0.0 $ safeRead ('0':'.':init x)
+ fromMaybe 0.0 $ safeRead (init x)
_ -> 0.0
+ if width > 0.0
+ then return $ width / 100.0
+ else return 0.0
pColgroup :: PandocMonad m => TagParser m [Double]
pColgroup = try $ do
@@ -774,7 +777,7 @@ pCode = try $ do
(TagOpen open attr') <- pSatisfy $ tagOpen (`elem` ["code","tt"]) (const True)
let attr = toStringAttr attr'
result <- manyTill pAnyTag (pCloses open)
- return $ B.codeWith (mkAttr attr) $ intercalate " " $ lines $ T.unpack $
+ return $ B.codeWith (mkAttr attr) $ unwords $ lines $ T.unpack $
innerText result
pSpan :: PandocMonad m => TagParser m Inlines
@@ -1224,7 +1227,7 @@ stripPrefixes = map stripPrefix
stripPrefix :: Tag Text -> Tag Text
stripPrefix (TagOpen s as) =
- TagOpen (stripPrefix' s) (map (stripPrefix' *** id) as)
+ TagOpen (stripPrefix' s) (map (first stripPrefix') as)
stripPrefix (TagClose s) = TagClose (stripPrefix' s)
stripPrefix x = x