Moved more from LaTeX reader to LaTeX.Parsing.
This commit is contained in:
parent
1e84178431
commit
7faa9d9064
2 changed files with 67 additions and 63 deletions
|
@ -757,36 +757,6 @@ opt = bracketed inline <|> (str <$> rawopt)
|
|||
paropt :: PandocMonad m => LP m Inlines
|
||||
paropt = parenWrapped inline
|
||||
|
||||
rawopt :: PandocMonad m => LP m Text
|
||||
rawopt = try $ do
|
||||
sp
|
||||
inner <- untokenize <$> bracketedToks
|
||||
sp
|
||||
return $ "[" <> inner <> "]"
|
||||
|
||||
skipopts :: PandocMonad m => LP m ()
|
||||
skipopts = skipMany (void overlaySpecification <|> void rawopt)
|
||||
|
||||
-- opts in angle brackets are used in beamer
|
||||
overlaySpecification :: PandocMonad m => LP m Text
|
||||
overlaySpecification = try $ do
|
||||
symbol '<'
|
||||
t <- untokenize <$> manyTill overlayTok (symbol '>')
|
||||
-- see issue #3368
|
||||
guard $ not (T.all isLetter t) ||
|
||||
t `elem` ["beamer","presentation", "trans",
|
||||
"handout","article", "second"]
|
||||
return $ "<" <> t <> ">"
|
||||
|
||||
overlayTok :: PandocMonad m => LP m Tok
|
||||
overlayTok =
|
||||
satisfyTok (\t ->
|
||||
case t of
|
||||
Tok _ Word _ -> True
|
||||
Tok _ Spaces _ -> True
|
||||
Tok _ Symbol c -> c `elem` ["-","+","@","|",":",","]
|
||||
_ -> False)
|
||||
|
||||
inBrackets :: Inlines -> Inlines
|
||||
inBrackets x = str "[" <> x <> str "]"
|
||||
|
||||
|
@ -1309,39 +1279,6 @@ processHBox = walk convert
|
|||
convert LineBreak = Str ""
|
||||
convert x = x
|
||||
|
||||
getRawCommand :: PandocMonad m => Text -> Text -> LP m Text
|
||||
getRawCommand name txt = do
|
||||
(_, rawargs) <- withRaw $
|
||||
case name of
|
||||
"write" -> do
|
||||
void $ satisfyTok isWordTok -- digits
|
||||
void braced
|
||||
"titleformat" -> do
|
||||
void braced
|
||||
skipopts
|
||||
void $ count 4 braced
|
||||
"def" ->
|
||||
void $ manyTill anyTok braced
|
||||
_ | isFontSizeCommand name -> return ()
|
||||
| otherwise -> do
|
||||
skipopts
|
||||
option "" (try dimenarg)
|
||||
void $ many braced
|
||||
return $ txt <> untokenize rawargs
|
||||
|
||||
isFontSizeCommand :: Text -> Bool
|
||||
isFontSizeCommand "tiny" = True
|
||||
isFontSizeCommand "scriptsize" = True
|
||||
isFontSizeCommand "footnotesize" = True
|
||||
isFontSizeCommand "small" = True
|
||||
isFontSizeCommand "normalsize" = True
|
||||
isFontSizeCommand "large" = True
|
||||
isFontSizeCommand "Large" = True
|
||||
isFontSizeCommand "LARGE" = True
|
||||
isFontSizeCommand "huge" = True
|
||||
isFontSizeCommand "Huge" = True
|
||||
isFontSizeCommand _ = False
|
||||
|
||||
isBlockCommand :: Text -> Bool
|
||||
isBlockCommand s =
|
||||
s `M.member` (blockCommands :: M.Map Text (LP PandocPure Blocks))
|
||||
|
|
|
@ -71,6 +71,10 @@ module Text.Pandoc.Readers.LaTeX.Parsing
|
|||
, verbEnv
|
||||
, begin_
|
||||
, end_
|
||||
, getRawCommand
|
||||
, skipopts
|
||||
, rawopt
|
||||
, overlaySpecification
|
||||
) where
|
||||
|
||||
import Control.Applicative (many, (<|>))
|
||||
|
@ -759,3 +763,66 @@ end_ t = try (do
|
|||
txt <- untokenize <$> braced
|
||||
guard $ t == txt) <?> ("\\end{" ++ T.unpack t ++ "}")
|
||||
|
||||
getRawCommand :: PandocMonad m => Text -> Text -> LP m Text
|
||||
getRawCommand name txt = do
|
||||
(_, rawargs) <- withRaw $
|
||||
case name of
|
||||
"write" -> do
|
||||
void $ satisfyTok isWordTok -- digits
|
||||
void braced
|
||||
"titleformat" -> do
|
||||
void braced
|
||||
skipopts
|
||||
void $ count 4 braced
|
||||
"def" ->
|
||||
void $ manyTill anyTok braced
|
||||
_ | isFontSizeCommand name -> return ()
|
||||
| otherwise -> do
|
||||
skipopts
|
||||
option "" (try dimenarg)
|
||||
void $ many braced
|
||||
return $ txt <> untokenize rawargs
|
||||
|
||||
skipopts :: PandocMonad m => LP m ()
|
||||
skipopts = skipMany (void overlaySpecification <|> void rawopt)
|
||||
|
||||
-- opts in angle brackets are used in beamer
|
||||
overlaySpecification :: PandocMonad m => LP m Text
|
||||
overlaySpecification = try $ do
|
||||
symbol '<'
|
||||
t <- untokenize <$> manyTill overlayTok (symbol '>')
|
||||
-- see issue #3368
|
||||
guard $ not (T.all isLetter t) ||
|
||||
t `elem` ["beamer","presentation", "trans",
|
||||
"handout","article", "second"]
|
||||
return $ "<" <> t <> ">"
|
||||
|
||||
overlayTok :: PandocMonad m => LP m Tok
|
||||
overlayTok =
|
||||
satisfyTok (\t ->
|
||||
case t of
|
||||
Tok _ Word _ -> True
|
||||
Tok _ Spaces _ -> True
|
||||
Tok _ Symbol c -> c `elem` ["-","+","@","|",":",","]
|
||||
_ -> False)
|
||||
|
||||
rawopt :: PandocMonad m => LP m Text
|
||||
rawopt = try $ do
|
||||
sp
|
||||
inner <- untokenize <$> bracketedToks
|
||||
sp
|
||||
return $ "[" <> inner <> "]"
|
||||
|
||||
isFontSizeCommand :: Text -> Bool
|
||||
isFontSizeCommand "tiny" = True
|
||||
isFontSizeCommand "scriptsize" = True
|
||||
isFontSizeCommand "footnotesize" = True
|
||||
isFontSizeCommand "small" = True
|
||||
isFontSizeCommand "normalsize" = True
|
||||
isFontSizeCommand "large" = True
|
||||
isFontSizeCommand "Large" = True
|
||||
isFontSizeCommand "LARGE" = True
|
||||
isFontSizeCommand "huge" = True
|
||||
isFontSizeCommand "Huge" = True
|
||||
isFontSizeCommand _ = False
|
||||
|
||||
|
|
Loading…
Reference in a new issue