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 diff --git a/test/command/5846.md b/test/command/5846.md new file mode 100644 index 000000000..ec00074d3 --- /dev/null +++ b/test/command/5846.md @@ -0,0 +1,170 @@ +``` +% pandoc --section-divs +::: {.mydiv} +# header 1a + +one + +# header 1b + +two +::: +^D +
+
+

header 1a

+

one

+
+
+

header 1b

+

two

+
+
+``` + +``` +% pandoc --section-divs +::: mydiv +# head 1 +## head 1.1 +# head 2 +::: + +## head 2.1 +^D +
+
+

head 1

+
+

head 1.1

+
+
+
+

head 2

+
+
+
+

head 2.1

+
+``` + +``` +% pandoc --section-divs +# One +## One A +::: fence +## One B +# Two +::: +^D +
+

One

+
+

One A

+
+
+
+

One B

+
+
+

Two

+
+
+
+``` + +``` +% pandoc --section-divs +# Beginning + +::: exterior + +At first... + +::: + +In the beginning... + +::: interior + +# Middle + +So it continued... + +::: + +# Ending + +::: exterior + +And finally... + +::: +^D +
+

Beginning

+
+

At first…

+
+

In the beginning…

+
+
+

Middle

+

So it continued…

+
+
+

Ending

+
+

And finally…

+
+
+``` + +``` +% pandoc --section-divs +::: part +# One +# Two +::: +::: part +# Three +# Four +# Five +::: +::: part +# Six +# Seven +# Eight +::: +^D +
+
+

One

+
+
+

Two

+
+
+
+
+

Three

+
+
+

Four

+
+
+

Five

+
+
+
+
+

Six

+
+
+

Seven

+
+
+

Eight

+
+
+```