From f76fe2ab56606528d4710cc6c40bceb5788c3906 Mon Sep 17 00:00:00 2001
From: Albert Krewinkel <albert@zeitkraut.de>
Date: Sat, 22 May 2021 13:29:13 +0200
Subject: [PATCH] HTML reader: simplify col width parsing

---
 src/Text/Pandoc/Readers/HTML/Table.hs | 22 +++++++++-------------
 1 file changed, 9 insertions(+), 13 deletions(-)

diff --git a/src/Text/Pandoc/Readers/HTML/Table.hs b/src/Text/Pandoc/Readers/HTML/Table.hs
index ad0b51253..6537bbce9 100644
--- a/src/Text/Pandoc/Readers/HTML/Table.hs
+++ b/src/Text/Pandoc/Readers/HTML/Table.hs
@@ -1,6 +1,5 @@
 {-# LANGUAGE LambdaCase        #-}
 {-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE ViewPatterns      #-}
 {- |
    Module      : Text.Pandoc.Readers.HTML.Table
    Copyright   : © 2006-2021 John MacFarlane,
@@ -42,18 +41,15 @@ pCol = try $ do
   skipMany pBlank
   optional $ pSatisfy (matchTagClose "col")
   skipMany pBlank
-  let width = case lookup "width" attribs of
-                Nothing -> case lookup "style" attribs of
-                  Just (T.stripPrefix "width:" -> Just xs) | T.any (== '%') xs ->
-                    fromMaybe 0.0 $ safeRead (T.filter
-                      (`notElem` (" \t\r\n%'\";" :: [Char])) xs)
-                  _ -> 0.0
-                Just (T.unsnoc -> Just (xs, '%')) ->
-                  fromMaybe 0.0 $ safeRead xs
-                _ -> 0.0
-  if width > 0.0
-    then return $ ColWidth $ width / 100.0
-    else return ColWidthDefault
+  let toColWidth = maybe ColWidthDefault (ColWidth . (/100.0)) . safeRead
+  return $ fromMaybe ColWidthDefault $
+    (case lookup "width" attribs >>= T.unsnoc of
+       Just (xs, '%') -> Just (toColWidth xs)
+       _ -> Nothing) <|>
+    (case lookup "style" attribs >>= T.stripPrefix "width" of
+        Just xs | T.any (== '%') xs -> Just . toColWidth $
+                  T.filter (`notElem` (" \t\r\n%'\";" :: [Char])) xs
+        _ -> Nothing)
 
 pColgroup :: PandocMonad m => TagParser m [ColWidth]
 pColgroup = try $ do