aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorJohn MacFarlane <jgm@berkeley.edu>2021-03-19 10:30:32 -0700
committerJohn MacFarlane <jgm@berkeley.edu>2021-03-19 10:30:32 -0700
commit8d5116381b20442bb3fa58dac1ef7d44db618823 (patch)
tree1d3b4f4d7b5f50819529a7c12f7df6147f3e6465 /src/Text
parenta31731b8e2825c5bc8d7fcc9a61ce92b9d28d040 (diff)
downloadpandoc-8d5116381b20442bb3fa58dac1ef7d44db618823.tar.gz
Use NonEmpty instead of minimumDef.
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs4
-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.hs5
4 files changed, 9 insertions, 8 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 32f7fc5af..851756065 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -68,7 +68,7 @@ import Text.Pandoc.Readers.LaTeX.Inline (acronymCommands, refCommands,
listingsLanguage)
import Text.Pandoc.Shared
import Text.Pandoc.Walk
-import Safe
+import Data.List.NonEmpty (nonEmpty)
-- for debugging:
-- import Text.Pandoc.Extensions (getDefaultExtensions)
@@ -96,7 +96,7 @@ parseLaTeX = do
let doc' = doc bs
let headerLevel (Header n _ _) = [n]
headerLevel _ = []
- let bottomLevel = minimumDef 1 $ query headerLevel doc'
+ let bottomLevel = maybe 1 minimum $ nonEmpty $ 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 c6f27118b..883434cdc 100644
--- a/src/Text/Pandoc/Readers/Org/Blocks.hs
+++ b/src/Text/Pandoc/Readers/Org/Blocks.hs
@@ -39,7 +39,7 @@ import Data.Functor (($>))
import Data.List (foldl', intersperse)
import Data.Maybe (fromMaybe, isJust, isNothing)
import Data.Text (Text)
-import Safe (minimumDef)
+import Data.List.NonEmpty (nonEmpty)
import qualified Data.Text as T
import qualified Text.Pandoc.Builder as B
@@ -543,7 +543,7 @@ include = try $ do
in case (minlvl >>= safeRead :: Maybe Int) of
Nothing -> blks
Just lvl -> let levels = Walk.query headerLevel blks
- curMin = minimumDef 0 levels
+ curMin = maybe 0 minimum $ nonEmpty 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 50ffd36ec..e26b902f1 100644
--- a/src/Text/Pandoc/Readers/Textile.hs
+++ b/src/Text/Pandoc/Readers/Textile.hs
@@ -53,7 +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)
+import Data.List.NonEmpty (nonEmpty)
-- | Parse a Textile text and return a Pandoc document.
readTextile :: PandocMonad m
@@ -377,7 +377,7 @@ table = try $ do
(toprow, rest)
_ -> (mempty, rawrows)
let nbOfCols = maximum $ map length (headers:rows)
- let aligns = map (minimumDef AlignDefault) $
+ let aligns = map (maybe AlignDefault minimum . nonEmpty) $
transpose $ map (map (snd . fst)) (headers:rows)
let toRow = Row nullAttr . map B.simpleCell
toHeaderRow l = [toRow l | not (null l)]
diff --git a/src/Text/Pandoc/Writers/Powerpoint/Output.hs b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
index b26a7ff3e..4dbf32c4e 100644
--- a/src/Text/Pandoc/Writers/Powerpoint/Output.hs
+++ b/src/Text/Pandoc/Writers/Powerpoint/Output.hs
@@ -50,7 +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)
+import Data.List.NonEmpty (nonEmpty)
-- |The 'EMU' type is used to specify sizes in English Metric Units.
type EMU = Integer
@@ -1428,7 +1428,8 @@ 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 = minimumDef 0 $ filter (1 <) $ map relId relsWeKeep
+ let minRelNotOne = maybe 0 minimum $ nonEmpty
+ $ filter (1 <) $ map relId relsWeKeep
modifyRelNum :: Int -> Int
modifyRelNum 1 = 1