aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2021-03-18 23:01:12 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2021-03-18 23:01:12 -0700
commit3428248debb14066e7fb1ef216927d3d62e3a43a (patch)
treeb25be4ecdf948a9e8813d9449874db8674e5c933
parentf0e4b9cc3cde01d64e25d331c5b4f3d62d2129b5 (diff)
downloadpandoc-3428248debb14066e7fb1ef216927d3d62e3a43a.tar.gz
Use minimumDef instead of minimum (partial function).
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs2
-rw-r--r--src/Text/Pandoc/Readers/Org/Blocks.hs4
-rw-r--r--src/Text/Pandoc/Readers/Textile.hs4
-rw-r--r--src/Text/Pandoc/Writers/Powerpoint/Output.hs7
4 files changed, 8 insertions, 9 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 21a563bed..32f7fc5af 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -96,7 +96,7 @@ parseLaTeX = do
let doc' = doc bs
let headerLevel (Header n _ _) = [n]
headerLevel _ = []
- let bottomLevel = minimumBound 1 $ query headerLevel doc'
+ let bottomLevel = minimumDef 1 $ query headerLevel doc'
let adjustHeaders m (Header n attr ils) = Header (n+m) attr ils
adjustHeaders _ x = x
let (Pandoc _ bs') =
diff --git a/src/Text/Pandoc/Readers/Org/Blocks.hs b/src/Text/Pandoc/Readers/Org/Blocks.hs
index d1aff701e..c6f27118b 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -39,6 +39,7 @@ import Data.Functor (($>))
import Data.List (foldl', intersperse)
import Data.Maybe (fromMaybe, isJust, isNothing)
import Data.Text (Text)
+import Safe (minimumDef)
import qualified Data.Text as T
import qualified Text.Pandoc.Builder as B
@@ -542,8 +543,7 @@ include = try $ do
in case (minlvl >>= safeRead :: Maybe Int) of
Nothing -> blks
Just lvl -> let levels = Walk.query headerLevel blks
- -- CAVE: partial function in else
- curMin = if null levels then 0 else minimum levels
+ curMin = minimumDef 0 levels
in Walk.walk (shiftHeader (curMin - lvl)) blks
headerLevel :: Block -> [Int]
diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs
index 99238c7f0..50ffd36ec 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -53,6 +53,7 @@ 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, tshow)
+import Safe (minimumDef)
-- | Parse a Textile text and return a Pandoc document.
readTextile :: PandocMonad m
@@ -376,7 +377,8 @@ table = try $ do
(toprow, rest)
_ -> (mempty, rawrows)
let nbOfCols = maximum $ map length (headers:rows)
- let aligns = map minimum $ transpose $ map (map (snd . fst)) (headers:rows)
+ let aligns = map (minimumDef AlignDefault) $
+ transpose $ map (map (snd . fst)) (headers:rows)
let toRow = Row nullAttr . map B.simpleCell
toHeaderRow l = [toRow l | not (null l)]
return $ B.table (B.simpleCaption $ B.plain caption)
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
index 5caeb0753..b26a7ff3e 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
@@ -50,6 +50,7 @@ import Text.Pandoc.Writers.Math (convertMath)
import Text.Pandoc.Writers.Powerpoint.Presentation
import Text.Pandoc.Shared (tshow)
import Skylighting (fromColor)
+import Safe (minimumDef)
-- |The 'EMU' type is used to specify sizes in English Metric Units.
type EMU = Integer
@@ -1427,11 +1428,7 @@ presentationToRels pres@(Presentation _ slides) = do
-- all relWithoutSlide rels (unless they're 1)
-- 3. If we have a notesmaster slide, we make space for that as well.
- let minRelNotOne = case filter (1<) $ map relId relsWeKeep of
- [] -> 0 -- doesn't matter in this case, since
- -- there will be nothing to map the
- -- function over
- l -> minimum l
+ let minRelNotOne = minimumDef 0 $ filter (1 <) $ map relId relsWeKeep
modifyRelNum :: Int -> Int
modifyRelNum 1 = 1