Use NonEmpty instead of minimumDef.
This commit is contained in:
parent
a31731b8e2
commit
8d5116381b
4 changed files with 9 additions and 8 deletions
|
@ -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') =
|
||||
|
|
|
@ -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]
|
||||
|
|
|
@ -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)]
|
||||
|
|
|
@ -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
|
||||
|
|
Loading…
Reference in a new issue