diff options
-rw-r--r-- | pandoc.cabal | 1 | ||||
-rw-r--r-- | src/Text/Pandoc/Parsing.hs | 2 | ||||
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 25 | ||||
-rw-r--r-- | test/command/1905.md | 30 |
4 files changed, 48 insertions, 10 deletions
diff --git a/pandoc.cabal b/pandoc.cabal index b0be28c33..bfc893b59 100644 --- a/pandoc.cabal +++ b/pandoc.cabal @@ -270,6 +270,7 @@ Library directory >= 1 && < 1.4, bytestring >= 0.9 && < 0.11, text >= 0.11 && < 1.3, + safe >= 0.3 && < 0.4, zip-archive >= 0.2.3.4 && < 0.4, HTTP >= 4000.0.5 && < 4000.4, texmath >= 0.9.3 && < 0.10, diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 3058185da..a84535875 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -928,7 +928,6 @@ data ParserState = ParserState stateIdentifiers :: Set.Set String, -- ^ Header identifiers used stateNextExample :: Int, -- ^ Number of next example stateExamples :: M.Map String Int, -- ^ Map from example labels to numbers - stateHasChapters :: Bool, -- ^ True if \chapter encountered stateMacros :: [Macro], -- ^ List of macros defined so far stateRstDefaultRole :: String, -- ^ Current rST default interpreted text role stateRstCustomRoles :: M.Map String (String, Maybe String, Attr), -- ^ Current rST custom text roles @@ -1036,7 +1035,6 @@ defaultParserState = stateIdentifiers = Set.empty, stateNextExample = 1, stateExamples = M.empty, - stateHasChapters = False, stateMacros = [], stateRstDefaultRole = "title-reference", stateRstCustomRoles = M.empty, diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 7018d2ce3..ae441a387 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -42,6 +42,7 @@ import Data.Char (chr, isAlphaNum, isLetter, ord) import Data.List (intercalate) import qualified Data.Map as M import Data.Maybe (fromMaybe, maybeToList) +import Safe (minimumDef) import System.FilePath (addExtension, replaceExtension, takeExtension) import Text.Pandoc.Builder import Text.Pandoc.Class (PandocMonad, PandocPure, lookupEnv, readFileFromDirs, @@ -72,7 +73,17 @@ parseLaTeX = do eof st <- getState let meta = stateMeta st - let (Pandoc _ bs') = doc bs + let doc' = doc bs + let headerLevel (Header n _ _) = [n] + headerLevel _ = [] + let bottomLevel = minimumDef 1 $ query headerLevel doc' + let adjustHeaders m (Header n attr ils) = Header (n+m) attr ils + adjustHeaders _ x = x + let (Pandoc _ bs') = + -- handle the case where you have \part or \chapter + (if bottomLevel < 1 + then walk (adjustHeaders (1 - bottomLevel)) + else id) doc' return $ Pandoc meta bs' type LP m = ParserT String ParserState m @@ -345,10 +356,10 @@ blockCommands = M.fromList $ -- Koma-script metadata commands , ("dedication", mempty <$ (skipopts *> tok >>= addMeta "dedication")) -- sectioning - , ("chapter", updateState (\s -> s{ stateHasChapters = True }) - *> section nullAttr 0) - , ("chapter*", updateState (\s -> s{ stateHasChapters = True }) - *> section ("",["unnumbered"],[]) 0) + , ("part", section nullAttr (-1)) + , ("part*", section nullAttr (-1)) + , ("chapter", section nullAttr 0) + , ("chapter*", section ("",["unnumbered"],[]) 0) , ("section", section nullAttr 1) , ("section*", section ("",["unnumbered"],[]) 1) , ("subsection", section nullAttr 2) @@ -444,13 +455,11 @@ authors = try $ do section :: PandocMonad m => Attr -> Int -> LP m Blocks section (ident, classes, kvs) lvl = do - hasChapters <- stateHasChapters `fmap` getState - let lvl' = if hasChapters then lvl + 1 else lvl skipopts contents <- grouped inline lab <- option ident $ try (spaces' >> controlSeq "label" >> spaces' >> braced) attr' <- registerHeader (lab, classes, kvs) contents - return $ headerWith attr' lvl' contents + return $ headerWith attr' lvl contents inlineCommand :: PandocMonad m => LP m Inlines inlineCommand = try $ do diff --git a/test/command/1905.md b/test/command/1905.md new file mode 100644 index 000000000..744d1c4d9 --- /dev/null +++ b/test/command/1905.md @@ -0,0 +1,30 @@ +``` +% pandoc -f latex-auto_identifiers -t html +\chapter{chapone} +\part{partone} +\chapter{chaptwo} +\section{secone} +^D +<h2>chapone</h2> +<h1>partone</h1> +<h2>chaptwo</h2> +<h3>secone</h3> +``` + +``` +% pandoc -f latex-auto_identifiers -t html +\chapter{chapone} +\chapter{chaptwo} +\section{secone} +^D +<h1>chapone</h1> +<h1>chaptwo</h1> +<h2>secone</h2> +``` + +``` +% pandoc -f latex-auto_identifiers -t html +\section{secone} +^D +<h1>secone</h1> +``` |