aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/LaTeX.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Readers/LaTeX.hs')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX.hs28
1 files changed, 25 insertions, 3 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs
index 01fca9f2b..406809dfc 100644
--- a/src/Text/Pandoc/Readers/LaTeX.hs
+++ b/src/Text/Pandoc/Readers/LaTeX.hs
@@ -35,7 +35,8 @@ module Text.Pandoc.Readers.LaTeX (
import Text.ParserCombinators.Parsec
import Text.Pandoc.Definition
-import Text.Pandoc.Shared
+import Text.Pandoc.Shared
+import Text.Pandoc.Parsing
import Data.Maybe ( fromMaybe )
import Data.Char ( chr )
import Data.List ( isPrefixOf, isSuffixOf )
@@ -167,16 +168,37 @@ block = choice [ hrule
--
header :: GenParser Char ParserState Block
-header = try $ do
+header = section <|> chapter
+
+chapter :: GenParser Char ParserState Block
+chapter = try $ do
+ string "\\chapter"
+ result <- headerWithLevel 1
+ updateState $ \s -> s{ stateHasChapters = True }
+ return result
+
+section :: GenParser Char ParserState Block
+section = try $ do
char '\\'
subs <- many (try (string "sub"))
base <- try (string "section" >> return 1) <|> (string "paragraph" >> return 4)
+ st <- getState
+ let lev = if stateHasChapters st
+ then length subs + base + 1
+ else length subs + base
+ headerWithLevel lev
+
+headerWithLevel :: Int -> GenParser Char ParserState Block
+headerWithLevel lev = try $ do
+ spaces
optional (char '*')
+ spaces
optional $ bracketedText '[' ']' -- alt title
+ spaces
char '{'
title' <- manyTill inline (char '}')
spaces
- return $ Header (length subs + base) (normalizeSpaces title')
+ return $ Header lev (normalizeSpaces title')
--
-- hrule block