diff options
author | John MacFarlane <jgm@berkeley.edu> | 2019-10-29 21:24:58 -0700 |
---|---|---|
committer | John MacFarlane <jgm@berkeley.edu> | 2019-10-29 21:24:58 -0700 |
commit | a796b655cd2046c1297d800e328ed9ef58251405 (patch) | |
tree | 10cf4d835aa54db0e0db9b378994f4c9bd3e7043 /src/Text | |
parent | 47566817c559557f5bc6c9c503afa1a37bf7df90 (diff) | |
download | pandoc-a796b655cd2046c1297d800e328ed9ef58251405.tar.gz |
Shared.makeSections: better behavior in some corner cases.
When a div surrounds multiple sections at the same level,
or a section of highre level followed by one of lower level,
then we just leave it as a div and create a new div for the
section.
Closes #5846, closes #5761.
Diffstat (limited to 'src/Text')
-rw-r--r-- | src/Text/Pandoc/Shared.hs | 10 |
1 files changed, 7 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 59e30feeb..ff97d16fb 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -1,12 +1,13 @@ -{-# LANGUAGE NoImplicitPrelude #-} +{-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE CPP #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ViewPatterns #-} -{-# LANGUAGE FlexibleInstances #-} +{-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE TypeSynonymInstances #-} +{-# LANGUAGE LambdaCase #-} {- | Module : Text.Pandoc.Shared Copyright : Copyright (C) 2006-2019 John MacFarlane @@ -533,7 +534,10 @@ makeSections numbering mbBaseLevel bs = return $ Div divattr (Header level' attr title' : sectionContents') : rest' go (Div (dident,dclasses,dkvs) - (Header level (ident,classes,kvs) title':ys) : xs) = do + (Header level (ident,classes,kvs) title':ys) : xs) + | all (\case + Header level' _ _ -> level' > level + _ -> True) ys = do inner <- go (Header level (ident,classes,kvs) title':ys) let inner' = case inner of |