diff options
Diffstat (limited to 'src/Text/Pandoc/Readers')
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Org/Blocks.hs | 4 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/Textile.hs | 4 |
3 files changed, 6 insertions, 6 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)] |