2017-03-04 13:03:41 +01:00
|
|
|
|
{-# LANGUAGE OverloadedStrings #-}
|
|
|
|
|
{-# LANGUAGE ScopedTypeVariables #-}
|
2007-11-03 23:27:58 +00:00
|
|
|
|
{-
|
2015-04-26 10:18:29 -07:00
|
|
|
|
Copyright (C) 2006-2015 John MacFarlane <jgm@berkeley.edu>
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
This program is free software; you can redistribute it and/or modify
|
|
|
|
|
it under the terms of the GNU General Public License as published by
|
|
|
|
|
the Free Software Foundation; either version 2 of the License, or
|
|
|
|
|
(at your option) any later version.
|
|
|
|
|
|
|
|
|
|
This program is distributed in the hope that it will be useful,
|
|
|
|
|
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
|
|
|
|
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
|
|
|
|
GNU General Public License for more details.
|
|
|
|
|
|
|
|
|
|
You should have received a copy of the GNU General Public License
|
|
|
|
|
along with this program; if not, write to the Free Software
|
|
|
|
|
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
|
|
|
|
-}
|
|
|
|
|
|
|
|
|
|
{- |
|
|
|
|
|
Module : Text.Pandoc.Readers.LaTeX
|
2015-04-26 10:18:29 -07:00
|
|
|
|
Copyright : Copyright (C) 2006-2015 John MacFarlane
|
2012-01-29 23:54:00 -08:00
|
|
|
|
License : GNU GPL, version 2 or above
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
|
|
|
|
Stability : alpha
|
|
|
|
|
Portability : portable
|
|
|
|
|
|
|
|
|
|
Conversion of LaTeX to 'Pandoc' document.
|
|
|
|
|
-}
|
2012-01-29 23:54:00 -08:00
|
|
|
|
module Text.Pandoc.Readers.LaTeX ( readLaTeX,
|
|
|
|
|
rawLaTeXInline,
|
|
|
|
|
rawLaTeXBlock,
|
2014-05-20 22:29:21 +02:00
|
|
|
|
inlineCommand,
|
2007-11-03 23:27:58 +00:00
|
|
|
|
) where
|
|
|
|
|
|
2017-03-04 13:03:41 +01:00
|
|
|
|
import Control.Applicative (many, optional, (<|>))
|
2011-01-05 12:25:47 -08:00
|
|
|
|
import Control.Monad
|
2017-03-04 13:03:41 +01:00
|
|
|
|
import Control.Monad.Except (throwError)
|
|
|
|
|
import Data.Char (chr, isAlphaNum, isLetter, ord)
|
2017-04-24 23:39:14 +02:00
|
|
|
|
import Data.List (intercalate, isPrefixOf)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
import qualified Data.Map as M
|
2017-03-04 13:03:41 +01:00
|
|
|
|
import Data.Maybe (fromMaybe, maybeToList)
|
2017-03-13 22:11:10 +01:00
|
|
|
|
import Safe (minimumDef)
|
2017-03-04 13:03:41 +01:00
|
|
|
|
import System.FilePath (addExtension, replaceExtension, takeExtension)
|
|
|
|
|
import Text.Pandoc.Builder
|
|
|
|
|
import Text.Pandoc.Class (PandocMonad, PandocPure, lookupEnv, readFileFromDirs,
|
|
|
|
|
report, setResourcePath)
|
2017-02-08 00:07:53 +01:00
|
|
|
|
import Text.Pandoc.Highlighting (fromListingsLanguage, languagesByExtension)
|
2015-04-02 21:09:08 -07:00
|
|
|
|
import Text.Pandoc.ImageSize (numUnit, showFl)
|
2017-03-04 13:03:41 +01:00
|
|
|
|
import Text.Pandoc.Logging
|
|
|
|
|
import Text.Pandoc.Options
|
|
|
|
|
import Text.Pandoc.Parsing hiding (many, mathDisplay, mathInline, optional,
|
|
|
|
|
space, (<|>))
|
|
|
|
|
import Text.Pandoc.Shared
|
|
|
|
|
import Text.Pandoc.Walk
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
|
|
|
|
-- | Parse LaTeX from string and return 'Pandoc' document.
|
2016-11-28 17:13:46 -05:00
|
|
|
|
readLaTeX :: PandocMonad m
|
|
|
|
|
=> ReaderOptions -- ^ Reader options
|
2009-10-04 22:09:23 +00:00
|
|
|
|
-> String -- ^ String to parse (assumes @'\n'@ line endings)
|
2016-11-28 17:13:46 -05:00
|
|
|
|
-> m Pandoc
|
|
|
|
|
readLaTeX opts ltx = do
|
|
|
|
|
parsed <- readWithM parseLaTeX def{ stateOptions = opts } ltx
|
|
|
|
|
case parsed of
|
|
|
|
|
Right result -> return result
|
2017-03-04 13:03:41 +01:00
|
|
|
|
Left e -> throwError e
|
2016-11-28 17:13:46 -05:00
|
|
|
|
|
|
|
|
|
parseLaTeX :: PandocMonad m => LP m Pandoc
|
2012-01-29 23:54:00 -08:00
|
|
|
|
parseLaTeX = do
|
|
|
|
|
bs <- blocks
|
|
|
|
|
eof
|
|
|
|
|
st <- getState
|
2013-05-10 22:53:35 -07:00
|
|
|
|
let meta = stateMeta st
|
2017-03-13 22:11:10 +01:00
|
|
|
|
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'
|
2013-05-10 22:53:35 -07:00
|
|
|
|
return $ Pandoc meta bs'
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
type LP m = ParserT String ParserState m
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
anyControlSeq :: PandocMonad m => LP m String
|
2012-01-29 23:54:00 -08:00
|
|
|
|
anyControlSeq = do
|
2007-11-03 23:27:58 +00:00
|
|
|
|
char '\\'
|
2012-01-29 23:54:00 -08:00
|
|
|
|
next <- option '\n' anyChar
|
2015-04-12 09:47:13 +03:00
|
|
|
|
case next of
|
|
|
|
|
'\n' -> return ""
|
|
|
|
|
c | isLetter c -> (c:) <$> (many letter <* optional sp)
|
|
|
|
|
| otherwise -> return [c]
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
controlSeq :: PandocMonad m => String -> LP m String
|
2012-01-29 23:54:00 -08:00
|
|
|
|
controlSeq name = try $ do
|
|
|
|
|
char '\\'
|
|
|
|
|
case name of
|
2017-03-04 13:03:41 +01:00
|
|
|
|
"" -> mzero
|
2012-01-29 23:54:00 -08:00
|
|
|
|
[c] | not (isLetter c) -> string [c]
|
2017-03-04 13:03:41 +01:00
|
|
|
|
cs -> string cs <* notFollowedBy letter <* optional sp
|
2007-11-03 23:27:58 +00:00
|
|
|
|
return name
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
dimenarg :: PandocMonad m => LP m String
|
2012-04-10 18:56:08 -07:00
|
|
|
|
dimenarg = try $ do
|
|
|
|
|
ch <- option "" $ string "="
|
|
|
|
|
num <- many1 digit
|
|
|
|
|
dim <- oneOfStrings ["pt","pc","in","bp","cm","mm","dd","cc","sp"]
|
|
|
|
|
return $ ch ++ num ++ dim
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
sp :: PandocMonad m => LP m ()
|
2015-12-12 09:31:51 -08:00
|
|
|
|
sp = whitespace <|> endline
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
whitespace :: PandocMonad m => LP m ()
|
2015-12-12 09:31:51 -08:00
|
|
|
|
whitespace = skipMany1 $ satisfy (\c -> c == ' ' || c == '\t')
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
endline :: PandocMonad m => LP m ()
|
2015-12-12 09:31:51 -08:00
|
|
|
|
endline = try (newline >> lookAhead anyChar >> notFollowedBy blankline)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
|
|
|
|
isLowerHex :: Char -> Bool
|
|
|
|
|
isLowerHex x = x >= '0' && x <= '9' || x >= 'a' && x <= 'f'
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
tildeEscape :: PandocMonad m => LP m Char
|
2012-01-29 23:54:00 -08:00
|
|
|
|
tildeEscape = try $ do
|
|
|
|
|
string "^^"
|
|
|
|
|
c <- satisfy (\x -> x >= '\0' && x <= '\128')
|
|
|
|
|
d <- if isLowerHex c
|
|
|
|
|
then option "" $ count 1 (satisfy isLowerHex)
|
|
|
|
|
else return ""
|
|
|
|
|
if null d
|
|
|
|
|
then case ord c of
|
|
|
|
|
x | x >= 64 && x <= 127 -> return $ chr (x - 64)
|
|
|
|
|
| otherwise -> return $ chr (x + 64)
|
|
|
|
|
else return $ chr $ read ('0':'x':c:d)
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
comment :: PandocMonad m => LP m ()
|
2012-01-29 23:54:00 -08:00
|
|
|
|
comment = do
|
|
|
|
|
char '%'
|
|
|
|
|
skipMany (satisfy (/='\n'))
|
2014-05-10 23:26:32 -07:00
|
|
|
|
optional newline
|
2012-01-29 23:54:00 -08:00
|
|
|
|
return ()
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
bgroup :: PandocMonad m => LP m ()
|
2015-12-22 11:06:06 -08:00
|
|
|
|
bgroup = try $ do
|
|
|
|
|
skipMany (spaceChar <|> try (newline <* notFollowedBy blankline))
|
|
|
|
|
() <$ char '{'
|
2012-04-07 16:16:43 -07:00
|
|
|
|
<|> () <$ controlSeq "bgroup"
|
|
|
|
|
<|> () <$ controlSeq "begingroup"
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
egroup :: PandocMonad m => LP m ()
|
2012-04-07 16:16:43 -07:00
|
|
|
|
egroup = () <$ char '}'
|
|
|
|
|
<|> () <$ controlSeq "egroup"
|
|
|
|
|
<|> () <$ controlSeq "endgroup"
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
grouped :: PandocMonad m => Monoid a => LP m a -> LP m a
|
2017-03-09 21:03:54 +01:00
|
|
|
|
grouped parser = try $ do
|
|
|
|
|
bgroup
|
|
|
|
|
-- first we check for an inner 'grouped', because
|
|
|
|
|
-- {{a,b}} should be parsed the same as {a,b}
|
|
|
|
|
try (grouped parser <* egroup)
|
|
|
|
|
<|> (mconcat <$> manyTill parser egroup)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
braced :: PandocMonad m => LP m String
|
2017-03-09 21:03:54 +01:00
|
|
|
|
braced = grouped chunk
|
|
|
|
|
where chunk =
|
|
|
|
|
many1 (satisfy (\c -> c /= '\\' && c /= '}' && c /= '{'))
|
|
|
|
|
<|> try (string "\\}")
|
|
|
|
|
<|> try (string "\\{")
|
|
|
|
|
<|> try (string "\\\\")
|
|
|
|
|
<|> ((\x -> "{" ++ x ++ "}") <$> braced)
|
|
|
|
|
<|> count 1 anyChar
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
bracketed :: PandocMonad m => Monoid a => LP m a -> LP m a
|
2012-01-29 23:54:00 -08:00
|
|
|
|
bracketed parser = try $ char '[' *> (mconcat <$> manyTill parser (char ']'))
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
mathDisplay :: PandocMonad m => LP m String -> LP m Inlines
|
2012-01-29 23:54:00 -08:00
|
|
|
|
mathDisplay p = displayMath <$> (try p >>= applyMacros' . trim)
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
mathInline :: PandocMonad m => LP m String -> LP m Inlines
|
2012-01-29 23:54:00 -08:00
|
|
|
|
mathInline p = math <$> (try p >>= applyMacros')
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
mathChars :: PandocMonad m => LP m String
|
2016-02-28 11:14:03 -08:00
|
|
|
|
mathChars =
|
|
|
|
|
concat <$> many (escapedChar
|
|
|
|
|
<|> (snd <$> withRaw braced)
|
|
|
|
|
<|> many1 (satisfy isOrdChar))
|
|
|
|
|
where escapedChar = try $ do char '\\'
|
|
|
|
|
c <- anyChar
|
|
|
|
|
return ['\\',c]
|
2017-03-04 13:03:41 +01:00
|
|
|
|
isOrdChar '$' = False
|
|
|
|
|
isOrdChar '{' = False
|
|
|
|
|
isOrdChar '}' = False
|
2016-02-28 11:14:03 -08:00
|
|
|
|
isOrdChar '\\' = False
|
2017-03-04 13:03:41 +01:00
|
|
|
|
isOrdChar _ = True
|
2012-02-07 19:40:26 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
quoted' :: PandocMonad m => (Inlines -> Inlines) -> LP m String -> LP m () -> LP m Inlines
|
2013-11-18 20:28:27 -08:00
|
|
|
|
quoted' f starter ender = do
|
|
|
|
|
startchs <- starter
|
2017-01-14 18:27:06 +01:00
|
|
|
|
smart <- extensionEnabled Ext_smart <$> getOption readerExtensions
|
2015-11-24 17:20:15 -08:00
|
|
|
|
if smart
|
|
|
|
|
then do
|
|
|
|
|
ils <- many (notFollowedBy ender >> inline)
|
|
|
|
|
(ender >> return (f (mconcat ils))) <|>
|
2016-01-11 12:16:25 -08:00
|
|
|
|
(<> mconcat ils) <$>
|
|
|
|
|
lit (case startchs of
|
2017-03-04 13:03:41 +01:00
|
|
|
|
"``" -> "“"
|
|
|
|
|
"`" -> "‘"
|
|
|
|
|
_ -> startchs)
|
2015-11-24 17:20:15 -08:00
|
|
|
|
else lit startchs
|
2013-11-18 20:28:27 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
doubleQuote :: PandocMonad m => LP m Inlines
|
2015-11-19 20:18:06 -08:00
|
|
|
|
doubleQuote = do
|
2015-11-24 17:20:15 -08:00
|
|
|
|
quoted' doubleQuoted (try $ string "``") (void $ try $ string "''")
|
|
|
|
|
<|> quoted' doubleQuoted (string "“") (void $ char '”')
|
|
|
|
|
-- the following is used by babel for localized quotes:
|
|
|
|
|
<|> quoted' doubleQuoted (try $ string "\"`") (void $ try $ string "\"'")
|
|
|
|
|
<|> quoted' doubleQuoted (string "\"") (void $ char '"')
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
singleQuote :: PandocMonad m => LP m Inlines
|
2015-11-19 20:18:06 -08:00
|
|
|
|
singleQuote = do
|
2017-01-14 18:27:06 +01:00
|
|
|
|
smart <- extensionEnabled Ext_smart <$> getOption readerExtensions
|
2015-11-19 20:18:06 -08:00
|
|
|
|
if smart
|
|
|
|
|
then quoted' singleQuoted (string "`") (try $ char '\'' >> notFollowedBy letter)
|
|
|
|
|
<|> quoted' singleQuoted (string "‘") (try $ char '’' >> notFollowedBy letter)
|
|
|
|
|
else str <$> many1 (oneOf "`\'‘’")
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
inline :: PandocMonad m => LP m Inlines
|
2012-01-29 23:54:00 -08:00
|
|
|
|
inline = (mempty <$ comment)
|
2015-12-12 09:31:51 -08:00
|
|
|
|
<|> (space <$ whitespace)
|
|
|
|
|
<|> (softbreak <$ endline)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
<|> inlineText
|
|
|
|
|
<|> inlineCommand
|
2014-12-16 12:27:04 -08:00
|
|
|
|
<|> inlineEnvironment
|
2013-09-28 11:53:19 -07:00
|
|
|
|
<|> inlineGroup
|
2012-01-29 23:54:00 -08:00
|
|
|
|
<|> (char '-' *> option (str "-")
|
2015-04-12 09:47:13 +03:00
|
|
|
|
(char '-' *> option (str "–") (str "—" <$ char '-')))
|
|
|
|
|
<|> doubleQuote
|
|
|
|
|
<|> singleQuote
|
2012-09-06 16:02:56 -07:00
|
|
|
|
<|> (str "”" <$ try (string "''"))
|
2013-11-18 20:28:27 -08:00
|
|
|
|
<|> (str "”" <$ char '”')
|
2012-01-29 23:54:00 -08:00
|
|
|
|
<|> (str "’" <$ char '\'')
|
2013-11-18 20:28:27 -08:00
|
|
|
|
<|> (str "’" <$ char '’')
|
2012-01-29 23:54:00 -08:00
|
|
|
|
<|> (str "\160" <$ char '~')
|
2015-04-12 09:47:13 +03:00
|
|
|
|
<|> mathDisplay (string "$$" *> mathChars <* string "$$")
|
|
|
|
|
<|> mathInline (char '$' *> mathChars <* char '$')
|
2012-08-08 23:18:19 -07:00
|
|
|
|
<|> (guardEnabled Ext_literate_haskell *> char '|' *> doLHSverb)
|
2012-09-06 16:02:56 -07:00
|
|
|
|
<|> (str . (:[]) <$> tildeEscape)
|
2016-12-05 11:09:51 +01:00
|
|
|
|
<|> (do res <- oneOf "#&~^'`\"[]"
|
|
|
|
|
pos <- getPosition
|
2017-02-10 23:59:47 +01:00
|
|
|
|
report $ ParsingUnescaped [res] pos
|
2016-12-05 11:09:51 +01:00
|
|
|
|
return $ str [res])
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
inlines :: PandocMonad m => LP m Inlines
|
2012-01-29 23:54:00 -08:00
|
|
|
|
inlines = mconcat <$> many (notFollowedBy (char '}') *> inline)
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
inlineGroup :: PandocMonad m => LP m Inlines
|
2013-09-28 11:53:19 -07:00
|
|
|
|
inlineGroup = do
|
|
|
|
|
ils <- grouped inline
|
|
|
|
|
if isNull ils
|
|
|
|
|
then return mempty
|
|
|
|
|
else return $ spanWith nullAttr ils
|
|
|
|
|
-- we need the span so we can detitlecase bibtex entries;
|
|
|
|
|
-- we need to know when something is {C}apitalized
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
block :: PandocMonad m => LP m Blocks
|
2012-01-29 23:54:00 -08:00
|
|
|
|
block = (mempty <$ comment)
|
2012-04-11 08:52:16 -07:00
|
|
|
|
<|> (mempty <$ ((spaceChar <|> newline) *> spaces))
|
2012-01-29 23:54:00 -08:00
|
|
|
|
<|> environment
|
2016-12-03 21:55:31 +01:00
|
|
|
|
<|> include
|
2013-01-28 10:50:58 -08:00
|
|
|
|
<|> macro
|
2012-01-29 23:54:00 -08:00
|
|
|
|
<|> blockCommand
|
|
|
|
|
<|> paragraph
|
2012-09-06 15:28:25 -07:00
|
|
|
|
<|> grouped block
|
2012-02-04 12:51:27 -08:00
|
|
|
|
<|> (mempty <$ char '&') -- loose & in table environment
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
blocks :: PandocMonad m => LP m Blocks
|
2012-01-29 23:54:00 -08:00
|
|
|
|
blocks = mconcat <$> many block
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
getRawCommand :: PandocMonad m => String -> LP m String
|
2015-03-21 22:39:07 +03:00
|
|
|
|
getRawCommand name' = do
|
2015-10-09 14:39:42 -07:00
|
|
|
|
rawargs <- withRaw (many (try (optional sp *> opt)) *>
|
|
|
|
|
option "" (try (optional sp *> dimenarg)) *>
|
2015-10-09 10:32:31 -07:00
|
|
|
|
many braced)
|
2015-03-21 22:39:07 +03:00
|
|
|
|
return $ '\\' : name' ++ snd rawargs
|
|
|
|
|
|
2015-04-12 09:47:13 +03:00
|
|
|
|
lookupListDefault :: (Ord k) => v -> [k] -> M.Map k v -> v
|
|
|
|
|
lookupListDefault d = (fromMaybe d .) . lookupList
|
|
|
|
|
where
|
|
|
|
|
lookupList l m = msum $ map (`M.lookup` m) l
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
blockCommand :: PandocMonad m => LP m Blocks
|
2012-01-29 23:54:00 -08:00
|
|
|
|
blockCommand = try $ do
|
|
|
|
|
name <- anyControlSeq
|
2012-09-09 18:27:52 -07:00
|
|
|
|
guard $ name /= "begin" && name /= "end"
|
2012-01-29 23:54:00 -08:00
|
|
|
|
star <- option "" (string "*" <* optional sp)
|
|
|
|
|
let name' = name ++ star
|
2015-03-21 22:39:07 +03:00
|
|
|
|
let raw = do
|
|
|
|
|
rawcommand <- getRawCommand name'
|
|
|
|
|
transformed <- applyMacros' rawcommand
|
2015-03-31 14:32:42 +03:00
|
|
|
|
guard $ transformed /= rawcommand
|
2015-03-30 06:42:15 +03:00
|
|
|
|
notFollowedBy $ parseFromString inlines transformed
|
2015-03-31 14:32:42 +03:00
|
|
|
|
parseFromString blocks transformed
|
2015-04-12 09:47:13 +03:00
|
|
|
|
lookupListDefault raw [name',name] blockCommands
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
|
|
|
|
inBrackets :: Inlines -> Inlines
|
2015-04-12 09:47:13 +03:00
|
|
|
|
inBrackets x = str "[" <> x <> str "]"
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2012-02-04 22:28:16 -08:00
|
|
|
|
-- eat an optional argument and one or more arguments in braces
|
2016-11-28 17:13:46 -05:00
|
|
|
|
ignoreInlines :: PandocMonad m => String -> (String, LP m Inlines)
|
2017-02-10 08:36:04 +01:00
|
|
|
|
ignoreInlines name = (name, p)
|
|
|
|
|
where
|
|
|
|
|
p = do oa <- optargs
|
|
|
|
|
let rawCommand = '\\':name ++ oa
|
|
|
|
|
let doraw = guardRaw >> return (rawInline "latex" rawCommand)
|
|
|
|
|
doraw <|> ignore rawCommand
|
|
|
|
|
|
|
|
|
|
guardRaw :: PandocMonad m => LP m ()
|
|
|
|
|
guardRaw = getOption readerExtensions >>= guard . extensionEnabled Ext_raw_tex
|
|
|
|
|
|
|
|
|
|
optargs :: PandocMonad m => LP m String
|
|
|
|
|
optargs = snd <$> withRaw (skipopts *> skipMany (try $ optional sp *> braced))
|
|
|
|
|
|
|
|
|
|
ignore :: (Monoid a, PandocMonad m) => String -> ParserT s u m a
|
|
|
|
|
ignore raw = do
|
2017-02-09 22:21:07 +01:00
|
|
|
|
pos <- getPosition
|
2017-02-10 23:59:47 +01:00
|
|
|
|
report $ SkippedContent raw pos
|
2017-02-09 22:21:07 +01:00
|
|
|
|
return mempty
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
ignoreBlocks :: PandocMonad m => String -> (String, LP m Blocks)
|
2017-02-10 08:36:04 +01:00
|
|
|
|
ignoreBlocks name = (name, p)
|
|
|
|
|
where
|
|
|
|
|
p = do oa <- optargs
|
|
|
|
|
let rawCommand = '\\':name ++ oa
|
|
|
|
|
let doraw = guardRaw >> return (rawBlock "latex" rawCommand)
|
|
|
|
|
doraw <|> ignore rawCommand
|
2012-02-04 22:28:16 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
blockCommands :: PandocMonad m => M.Map String (LP m Blocks)
|
2012-02-04 22:28:16 -08:00
|
|
|
|
blockCommands = M.fromList $
|
2012-02-09 17:45:40 -08:00
|
|
|
|
[ ("par", mempty <$ skipopts)
|
2017-02-14 23:11:25 +01:00
|
|
|
|
, ("parbox", braced >> grouped blocks)
|
2015-03-14 23:11:04 -07:00
|
|
|
|
, ("title", mempty <$ (skipopts *>
|
|
|
|
|
(grouped inline >>= addMeta "title")
|
|
|
|
|
<|> (grouped block >>= addMeta "title")))
|
2013-05-10 22:53:35 -07:00
|
|
|
|
, ("subtitle", mempty <$ (skipopts *> tok >>= addMeta "subtitle"))
|
2012-02-09 17:45:40 -08:00
|
|
|
|
, ("author", mempty <$ (skipopts *> authors))
|
|
|
|
|
-- -- in letter class, temp. store address & sig as title, author
|
2013-05-10 22:53:35 -07:00
|
|
|
|
, ("address", mempty <$ (skipopts *> tok >>= addMeta "address"))
|
2012-02-09 17:45:40 -08:00
|
|
|
|
, ("signature", mempty <$ (skipopts *> authors))
|
2013-05-10 22:53:35 -07:00
|
|
|
|
, ("date", mempty <$ (skipopts *> tok >>= addMeta "date"))
|
2017-02-27 14:16:05 +01:00
|
|
|
|
-- Koma-script metadata commands
|
|
|
|
|
, ("dedication", mempty <$ (skipopts *> tok >>= addMeta "dedication"))
|
2012-02-04 22:28:16 -08:00
|
|
|
|
-- sectioning
|
2017-03-13 22:11:10 +01:00
|
|
|
|
, ("part", section nullAttr (-1))
|
|
|
|
|
, ("part*", section nullAttr (-1))
|
|
|
|
|
, ("chapter", section nullAttr 0)
|
|
|
|
|
, ("chapter*", section ("",["unnumbered"],[]) 0)
|
2013-02-20 09:59:31 -08:00
|
|
|
|
, ("section", section nullAttr 1)
|
|
|
|
|
, ("section*", section ("",["unnumbered"],[]) 1)
|
|
|
|
|
, ("subsection", section nullAttr 2)
|
|
|
|
|
, ("subsection*", section ("",["unnumbered"],[]) 2)
|
|
|
|
|
, ("subsubsection", section nullAttr 3)
|
|
|
|
|
, ("subsubsection*", section ("",["unnumbered"],[]) 3)
|
|
|
|
|
, ("paragraph", section nullAttr 4)
|
|
|
|
|
, ("paragraph*", section ("",["unnumbered"],[]) 4)
|
|
|
|
|
, ("subparagraph", section nullAttr 5)
|
|
|
|
|
, ("subparagraph*", section ("",["unnumbered"],[]) 5)
|
2012-02-05 09:28:56 -08:00
|
|
|
|
-- beamer slides
|
2013-02-20 09:59:31 -08:00
|
|
|
|
, ("frametitle", section nullAttr 3)
|
|
|
|
|
, ("framesubtitle", section nullAttr 4)
|
2012-02-05 09:28:56 -08:00
|
|
|
|
-- letters
|
2012-02-09 17:45:40 -08:00
|
|
|
|
, ("opening", (para . trimInlines) <$> (skipopts *> tok))
|
|
|
|
|
, ("closing", skipopts *> closing)
|
2012-02-05 09:28:56 -08:00
|
|
|
|
--
|
2013-02-11 17:39:52 -08:00
|
|
|
|
, ("hrule", pure horizontalRule)
|
2016-11-19 22:45:36 +01:00
|
|
|
|
, ("strut", pure mempty)
|
2012-02-09 17:45:40 -08:00
|
|
|
|
, ("rule", skipopts *> tok *> tok *> pure horizontalRule)
|
2015-04-12 09:47:13 +03:00
|
|
|
|
, ("item", skipopts *> looseItem)
|
2012-02-09 17:45:40 -08:00
|
|
|
|
, ("documentclass", skipopts *> braced *> preamble)
|
2012-05-22 15:38:11 -07:00
|
|
|
|
, ("centerline", (para . trimInlines) <$> (skipopts *> tok))
|
2014-12-15 21:49:35 -08:00
|
|
|
|
, ("caption", skipopts *> setCaption)
|
2014-05-11 22:52:29 -07:00
|
|
|
|
, ("bibliography", mempty <$ (skipopts *> braced >>=
|
|
|
|
|
addMeta "bibliography" . splitBibs))
|
2014-05-12 13:06:06 -07:00
|
|
|
|
, ("addbibresource", mempty <$ (skipopts *> braced >>=
|
|
|
|
|
addMeta "bibliography" . splitBibs))
|
2017-02-08 00:07:53 +01:00
|
|
|
|
-- includes
|
|
|
|
|
, ("lstinputlisting", inputListing)
|
2017-02-24 15:34:41 +01:00
|
|
|
|
, ("graphicspath", graphicsPath)
|
2017-03-01 21:05:29 +01:00
|
|
|
|
-- hyperlink
|
|
|
|
|
, ("hypertarget", braced >> grouped block)
|
2012-02-04 22:28:16 -08:00
|
|
|
|
] ++ map ignoreBlocks
|
|
|
|
|
-- these commands will be ignored unless --parse-raw is specified,
|
|
|
|
|
-- in which case they will appear as raw latex blocks
|
|
|
|
|
[ "newcommand", "renewcommand", "newenvironment", "renewenvironment"
|
|
|
|
|
-- newcommand, etc. should be parsed by macro, but we need this
|
|
|
|
|
-- here so these aren't parsed as inline commands to ignore
|
|
|
|
|
, "special", "pdfannot", "pdfstringdef"
|
2014-05-11 22:52:29 -07:00
|
|
|
|
, "bibliographystyle"
|
2012-02-06 12:41:34 -08:00
|
|
|
|
, "maketitle", "makeindex", "makeglossary"
|
2012-02-04 22:28:16 -08:00
|
|
|
|
, "addcontentsline", "addtocontents", "addtocounter"
|
|
|
|
|
-- \ignore{} is used conventionally in literate haskell for definitions
|
|
|
|
|
-- that are to be processed by the compiler but not printed.
|
|
|
|
|
, "ignore"
|
|
|
|
|
, "hyperdef"
|
|
|
|
|
, "markboth", "markright", "markleft"
|
2017-02-25 10:28:56 +01:00
|
|
|
|
, "hspace", "vspace"
|
2015-04-22 08:48:25 -07:00
|
|
|
|
, "newpage"
|
2017-03-06 21:46:38 +01:00
|
|
|
|
, "clearpage"
|
|
|
|
|
, "pagebreak"
|
2012-01-29 23:54:00 -08:00
|
|
|
|
]
|
|
|
|
|
|
2017-02-24 15:34:41 +01:00
|
|
|
|
graphicsPath :: PandocMonad m => LP m Blocks
|
|
|
|
|
graphicsPath = do
|
|
|
|
|
ps <- bgroup *> (manyTill braced egroup)
|
|
|
|
|
setResourcePath (".":ps)
|
|
|
|
|
return mempty
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
addMeta :: PandocMonad m => ToMetaValue a => String -> a -> LP m ()
|
2014-04-26 12:14:42 -07:00
|
|
|
|
addMeta field val = updateState $ \st ->
|
|
|
|
|
st{ stateMeta = addMetaField field val $ stateMeta st }
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2014-05-11 22:52:29 -07:00
|
|
|
|
splitBibs :: String -> [Inlines]
|
|
|
|
|
splitBibs = map (str . flip replaceExtension "bib" . trim) . splitBy (==',')
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
setCaption :: PandocMonad m => LP m Blocks
|
2014-12-15 21:49:35 -08:00
|
|
|
|
setCaption = do
|
|
|
|
|
ils <- tok
|
|
|
|
|
mblabel <- option Nothing $
|
2015-03-14 23:12:04 -07:00
|
|
|
|
try $ spaces' >> controlSeq "label" >> (Just <$> tok)
|
2014-12-15 21:49:35 -08:00
|
|
|
|
let ils' = case mblabel of
|
|
|
|
|
Just lab -> ils <> spanWith
|
|
|
|
|
("",[],[("data-label", stringify lab)]) mempty
|
|
|
|
|
Nothing -> ils
|
|
|
|
|
updateState $ \st -> st{ stateCaption = Just ils' }
|
2014-03-25 23:10:43 -07:00
|
|
|
|
return mempty
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
resetCaption :: PandocMonad m => LP m ()
|
2014-03-25 23:10:43 -07:00
|
|
|
|
resetCaption = updateState $ \st -> st{ stateCaption = Nothing }
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
authors :: PandocMonad m => LP m ()
|
2012-01-29 23:54:00 -08:00
|
|
|
|
authors = try $ do
|
2017-03-05 11:17:03 +01:00
|
|
|
|
bgroup
|
2012-02-05 09:06:34 -08:00
|
|
|
|
let oneAuthor = mconcat <$>
|
2012-05-11 20:50:00 -07:00
|
|
|
|
many1 (notFollowedBy' (controlSeq "and") >>
|
|
|
|
|
(inline <|> mempty <$ blockCommand))
|
|
|
|
|
-- skip e.g. \vspace{10pt}
|
2012-01-29 23:54:00 -08:00
|
|
|
|
auths <- sepBy oneAuthor (controlSeq "and")
|
2017-03-05 11:17:03 +01:00
|
|
|
|
egroup
|
2014-04-26 12:14:42 -07:00
|
|
|
|
addMeta "author" (map trimInlines auths)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
section :: PandocMonad m => Attr -> Int -> LP m Blocks
|
2013-08-16 12:40:38 -07:00
|
|
|
|
section (ident, classes, kvs) lvl = do
|
2012-02-09 17:45:40 -08:00
|
|
|
|
skipopts
|
2012-01-29 23:54:00 -08:00
|
|
|
|
contents <- grouped inline
|
2015-03-14 23:12:04 -07:00
|
|
|
|
lab <- option ident $ try (spaces' >> controlSeq "label" >> spaces' >> braced)
|
2013-09-01 09:13:31 -07:00
|
|
|
|
attr' <- registerHeader (lab, classes, kvs) contents
|
2017-03-13 22:11:10 +01:00
|
|
|
|
return $ headerWith attr' lvl contents
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
inlineCommand :: PandocMonad m => LP m Inlines
|
2012-01-29 23:54:00 -08:00
|
|
|
|
inlineCommand = try $ do
|
2017-02-22 21:15:25 +01:00
|
|
|
|
(name, raw') <- withRaw anyControlSeq
|
2012-09-09 18:21:53 -07:00
|
|
|
|
guard $ name /= "begin" && name /= "end"
|
2012-01-29 23:54:00 -08:00
|
|
|
|
star <- option "" (string "*")
|
|
|
|
|
let name' = name ++ star
|
2012-12-12 19:28:33 -08:00
|
|
|
|
let raw = do
|
2017-02-27 00:40:33 +01:00
|
|
|
|
guard $ not (isBlockCommand name)
|
2016-11-20 21:17:41 +01:00
|
|
|
|
rawargs <- withRaw
|
2017-02-27 00:40:33 +01:00
|
|
|
|
(skipangles *> skipopts *> option "" dimenarg *> many braced)
|
2017-02-22 21:15:25 +01:00
|
|
|
|
let rawcommand = raw' ++ star ++ snd rawargs
|
2012-12-12 19:28:33 -08:00
|
|
|
|
transformed <- applyMacros' rawcommand
|
2017-02-27 00:40:33 +01:00
|
|
|
|
exts <- getOption readerExtensions
|
2012-12-12 19:28:33 -08:00
|
|
|
|
if transformed /= rawcommand
|
|
|
|
|
then parseFromString inlines transformed
|
2017-02-06 23:33:23 +01:00
|
|
|
|
else if extensionEnabled Ext_raw_tex exts
|
2012-12-12 19:28:33 -08:00
|
|
|
|
then return $ rawInline "latex" rawcommand
|
2017-02-10 08:36:04 +01:00
|
|
|
|
else ignore rawcommand
|
2017-02-27 00:40:33 +01:00
|
|
|
|
(lookupListDefault raw [name',name] inlineCommands <*
|
2016-01-31 10:52:46 -08:00
|
|
|
|
optional (try (string "{}")))
|
2012-04-15 17:40:58 -07:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
unlessParseRaw :: PandocMonad m => LP m ()
|
2017-02-06 23:33:23 +01:00
|
|
|
|
unlessParseRaw = getOption readerExtensions >>=
|
|
|
|
|
guard . not . extensionEnabled Ext_raw_tex
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
|
|
|
|
isBlockCommand :: String -> Bool
|
2016-11-28 17:13:46 -05:00
|
|
|
|
isBlockCommand s = s `M.member` (blockCommands :: M.Map String (LP PandocPure Blocks))
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2014-12-16 12:27:04 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
inlineEnvironments :: PandocMonad m => M.Map String (LP m Inlines)
|
2014-12-16 12:27:04 -08:00
|
|
|
|
inlineEnvironments = M.fromList
|
|
|
|
|
[ ("displaymath", mathEnv id Nothing "displaymath")
|
2016-01-29 10:11:45 -08:00
|
|
|
|
, ("math", math <$> verbEnv "math")
|
2014-12-16 12:27:04 -08:00
|
|
|
|
, ("equation", mathEnv id Nothing "equation")
|
|
|
|
|
, ("equation*", mathEnv id Nothing "equation*")
|
|
|
|
|
, ("gather", mathEnv id (Just "gathered") "gather")
|
|
|
|
|
, ("gather*", mathEnv id (Just "gathered") "gather*")
|
|
|
|
|
, ("multline", mathEnv id (Just "gathered") "multline")
|
|
|
|
|
, ("multline*", mathEnv id (Just "gathered") "multline*")
|
|
|
|
|
, ("eqnarray", mathEnv id (Just "aligned") "eqnarray")
|
|
|
|
|
, ("eqnarray*", mathEnv id (Just "aligned") "eqnarray*")
|
|
|
|
|
, ("align", mathEnv id (Just "aligned") "align")
|
|
|
|
|
, ("align*", mathEnv id (Just "aligned") "align*")
|
|
|
|
|
, ("alignat", mathEnv id (Just "aligned") "alignat")
|
|
|
|
|
, ("alignat*", mathEnv id (Just "aligned") "alignat*")
|
|
|
|
|
]
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
inlineCommands :: PandocMonad m => M.Map String (LP m Inlines)
|
2012-02-04 22:28:16 -08:00
|
|
|
|
inlineCommands = M.fromList $
|
2014-06-16 19:18:33 -07:00
|
|
|
|
[ ("emph", extractSpaces emph <$> tok)
|
|
|
|
|
, ("textit", extractSpaces emph <$> tok)
|
|
|
|
|
, ("textsl", extractSpaces emph <$> tok)
|
|
|
|
|
, ("textsc", extractSpaces smallcaps <$> tok)
|
2017-03-05 20:21:29 +01:00
|
|
|
|
, ("textsf", extractSpaces (spanWith ("",["sans-serif"],[])) <$> tok)
|
|
|
|
|
, ("textmd", extractSpaces (spanWith ("",["medium"],[])) <$> tok)
|
|
|
|
|
, ("textrm", extractSpaces (spanWith ("",["roman"],[])) <$> tok)
|
|
|
|
|
, ("textup", extractSpaces (spanWith ("",["upright"],[])) <$> tok)
|
2017-04-26 12:05:13 +02:00
|
|
|
|
, ("texttt", ttfamily)
|
2014-06-16 19:18:33 -07:00
|
|
|
|
, ("sout", extractSpaces strikeout <$> tok)
|
|
|
|
|
, ("textsuperscript", extractSpaces superscript <$> tok)
|
|
|
|
|
, ("textsubscript", extractSpaces subscript <$> tok)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("textbackslash", lit "\\")
|
|
|
|
|
, ("backslash", lit "\\")
|
2012-09-04 23:21:15 -07:00
|
|
|
|
, ("slash", lit "/")
|
2014-06-16 19:18:33 -07:00
|
|
|
|
, ("textbf", extractSpaces strong <$> tok)
|
|
|
|
|
, ("textnormal", extractSpaces (spanWith ("",["nodecor"],[])) <$> tok)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("ldots", lit "…")
|
2017-04-26 12:03:07 +02:00
|
|
|
|
, ("vdots", lit "\8942")
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("dots", lit "…")
|
|
|
|
|
, ("mdots", lit "…")
|
|
|
|
|
, ("sim", lit "~")
|
2012-04-15 17:40:58 -07:00
|
|
|
|
, ("label", unlessParseRaw >> (inBrackets <$> tok))
|
|
|
|
|
, ("ref", unlessParseRaw >> (inBrackets <$> tok))
|
2014-12-15 10:34:59 -08:00
|
|
|
|
, ("textgreek", tok)
|
2014-10-03 11:33:02 +10:00
|
|
|
|
, ("sep", lit ",")
|
2014-12-15 20:27:42 -08:00
|
|
|
|
, ("cref", unlessParseRaw >> (inBrackets <$> tok)) -- from cleveref.sty
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("(", mathInline $ manyTill anyChar (try $ string "\\)"))
|
|
|
|
|
, ("[", mathDisplay $ manyTill anyChar (try $ string "\\]"))
|
2015-04-12 09:47:13 +03:00
|
|
|
|
, ("ensuremath", mathInline braced)
|
2014-12-15 10:03:19 -08:00
|
|
|
|
, ("texorpdfstring", (\_ x -> x) <$> tok <*> tok)
|
2012-02-04 22:28:16 -08:00
|
|
|
|
, ("P", lit "¶")
|
|
|
|
|
, ("S", lit "§")
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("$", lit "$")
|
|
|
|
|
, ("%", lit "%")
|
|
|
|
|
, ("&", lit "&")
|
|
|
|
|
, ("#", lit "#")
|
|
|
|
|
, ("_", lit "_")
|
|
|
|
|
, ("{", lit "{")
|
|
|
|
|
, ("}", lit "}")
|
|
|
|
|
-- old TeX commands
|
2014-06-16 19:18:33 -07:00
|
|
|
|
, ("em", extractSpaces emph <$> inlines)
|
|
|
|
|
, ("it", extractSpaces emph <$> inlines)
|
|
|
|
|
, ("sl", extractSpaces emph <$> inlines)
|
|
|
|
|
, ("bf", extractSpaces strong <$> inlines)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("rm", inlines)
|
2014-06-16 19:18:33 -07:00
|
|
|
|
, ("itshape", extractSpaces emph <$> inlines)
|
|
|
|
|
, ("slshape", extractSpaces emph <$> inlines)
|
|
|
|
|
, ("scshape", extractSpaces smallcaps <$> inlines)
|
|
|
|
|
, ("bfseries", extractSpaces strong <$> inlines)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("/", pure mempty) -- italic correction
|
|
|
|
|
, ("aa", lit "å")
|
|
|
|
|
, ("AA", lit "Å")
|
|
|
|
|
, ("ss", lit "ß")
|
|
|
|
|
, ("o", lit "ø")
|
|
|
|
|
, ("O", lit "Ø")
|
|
|
|
|
, ("L", lit "Ł")
|
|
|
|
|
, ("l", lit "ł")
|
|
|
|
|
, ("ae", lit "æ")
|
|
|
|
|
, ("AE", lit "Æ")
|
2013-08-16 14:48:24 +10:00
|
|
|
|
, ("oe", lit "œ")
|
|
|
|
|
, ("OE", lit "Œ")
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("pounds", lit "£")
|
|
|
|
|
, ("euro", lit "€")
|
|
|
|
|
, ("copyright", lit "©")
|
2013-03-31 21:08:19 -07:00
|
|
|
|
, ("textasciicircum", lit "^")
|
|
|
|
|
, ("textasciitilde", lit "~")
|
2016-11-01 10:17:15 +01:00
|
|
|
|
, ("H", try $ tok >>= accent hungarumlaut)
|
2012-02-25 09:55:38 -08:00
|
|
|
|
, ("`", option (str "`") $ try $ tok >>= accent grave)
|
|
|
|
|
, ("'", option (str "'") $ try $ tok >>= accent acute)
|
|
|
|
|
, ("^", option (str "^") $ try $ tok >>= accent circ)
|
|
|
|
|
, ("~", option (str "~") $ try $ tok >>= accent tilde)
|
|
|
|
|
, ("\"", option (str "\"") $ try $ tok >>= accent umlaut)
|
|
|
|
|
, (".", option (str ".") $ try $ tok >>= accent dot)
|
|
|
|
|
, ("=", option (str "=") $ try $ tok >>= accent macron)
|
|
|
|
|
, ("c", option (str "c") $ try $ tok >>= accent cedilla)
|
2013-07-25 10:00:11 -07:00
|
|
|
|
, ("v", option (str "v") $ try $ tok >>= accent hacek)
|
2013-08-16 10:03:54 +10:00
|
|
|
|
, ("u", option (str "u") $ try $ tok >>= accent breve)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("i", lit "i")
|
2015-03-14 23:12:04 -07:00
|
|
|
|
, ("\\", linebreak <$ (optional (bracketed inline) *> spaces'))
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, (",", pure mempty)
|
|
|
|
|
, ("@", pure mempty)
|
|
|
|
|
, (" ", lit "\160")
|
2012-02-04 22:28:16 -08:00
|
|
|
|
, ("ps", pure $ str "PS." <> space)
|
2012-02-05 08:50:25 -08:00
|
|
|
|
, ("TeX", lit "TeX")
|
|
|
|
|
, ("LaTeX", lit "LaTeX")
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("bar", lit "|")
|
|
|
|
|
, ("textless", lit "<")
|
|
|
|
|
, ("textgreater", lit ">")
|
2017-03-05 11:17:03 +01:00
|
|
|
|
, ("thanks", note <$> grouped block)
|
|
|
|
|
, ("footnote", note <$> grouped block)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("verb", doverb)
|
2017-03-29 14:49:46 +02:00
|
|
|
|
, ("lstinline", dolstinline)
|
2013-12-13 19:16:04 -05:00
|
|
|
|
, ("Verb", doverb)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("url", (unescapeURL <$> braced) >>= \url ->
|
2013-01-06 20:51:51 -08:00
|
|
|
|
pure (link url "" (str url)))
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("href", (unescapeURL <$> braced <* optional sp) >>= \url ->
|
|
|
|
|
tok >>= \lab ->
|
|
|
|
|
pure (link url "" lab))
|
2015-04-02 21:09:08 -07:00
|
|
|
|
, ("includegraphics", do options <- option [] keyvals
|
2016-07-01 15:47:06 -07:00
|
|
|
|
src <- unescapeURL . removeDoubleQuotes <$> braced
|
2015-04-02 21:09:08 -07:00
|
|
|
|
mkImage options src)
|
2012-10-15 20:15:34 -07:00
|
|
|
|
, ("enquote", enquote)
|
2016-06-29 07:58:33 -07:00
|
|
|
|
, ("cite", citation "cite" NormalCitation False)
|
|
|
|
|
, ("Cite", citation "Cite" NormalCitation False)
|
2012-10-21 23:16:23 -07:00
|
|
|
|
, ("citep", citation "citep" NormalCitation False)
|
|
|
|
|
, ("citep*", citation "citep*" NormalCitation False)
|
|
|
|
|
, ("citeal", citation "citeal" NormalCitation False)
|
|
|
|
|
, ("citealp", citation "citealp" NormalCitation False)
|
|
|
|
|
, ("citealp*", citation "citealp*" NormalCitation False)
|
|
|
|
|
, ("autocite", citation "autocite" NormalCitation False)
|
2014-11-25 10:03:43 -08:00
|
|
|
|
, ("smartcite", citation "smartcite" NormalCitation False)
|
2012-10-21 23:16:23 -07:00
|
|
|
|
, ("footcite", inNote <$> citation "footcite" NormalCitation False)
|
|
|
|
|
, ("parencite", citation "parencite" NormalCitation False)
|
|
|
|
|
, ("supercite", citation "supercite" NormalCitation False)
|
|
|
|
|
, ("footcitetext", inNote <$> citation "footcitetext" NormalCitation False)
|
|
|
|
|
, ("citeyearpar", citation "citeyearpar" SuppressAuthor False)
|
|
|
|
|
, ("citeyear", citation "citeyear" SuppressAuthor False)
|
|
|
|
|
, ("autocite*", citation "autocite*" SuppressAuthor False)
|
|
|
|
|
, ("cite*", citation "cite*" SuppressAuthor False)
|
|
|
|
|
, ("parencite*", citation "parencite*" SuppressAuthor False)
|
|
|
|
|
, ("textcite", citation "textcite" AuthorInText False)
|
|
|
|
|
, ("citet", citation "citet" AuthorInText False)
|
|
|
|
|
, ("citet*", citation "citet*" AuthorInText False)
|
|
|
|
|
, ("citealt", citation "citealt" AuthorInText False)
|
|
|
|
|
, ("citealt*", citation "citealt*" AuthorInText False)
|
|
|
|
|
, ("textcites", citation "textcites" AuthorInText True)
|
|
|
|
|
, ("cites", citation "cites" NormalCitation True)
|
|
|
|
|
, ("autocites", citation "autocites" NormalCitation True)
|
|
|
|
|
, ("footcites", inNote <$> citation "footcites" NormalCitation True)
|
|
|
|
|
, ("parencites", citation "parencites" NormalCitation True)
|
|
|
|
|
, ("supercites", citation "supercites" NormalCitation True)
|
|
|
|
|
, ("footcitetexts", inNote <$> citation "footcitetexts" NormalCitation True)
|
|
|
|
|
, ("Autocite", citation "Autocite" NormalCitation False)
|
2014-11-25 10:03:43 -08:00
|
|
|
|
, ("Smartcite", citation "Smartcite" NormalCitation False)
|
2012-10-21 23:16:23 -07:00
|
|
|
|
, ("Footcite", citation "Footcite" NormalCitation False)
|
|
|
|
|
, ("Parencite", citation "Parencite" NormalCitation False)
|
|
|
|
|
, ("Supercite", citation "Supercite" NormalCitation False)
|
|
|
|
|
, ("Footcitetext", inNote <$> citation "Footcitetext" NormalCitation False)
|
|
|
|
|
, ("Citeyearpar", citation "Citeyearpar" SuppressAuthor False)
|
|
|
|
|
, ("Citeyear", citation "Citeyear" SuppressAuthor False)
|
|
|
|
|
, ("Autocite*", citation "Autocite*" SuppressAuthor False)
|
|
|
|
|
, ("Cite*", citation "Cite*" SuppressAuthor False)
|
|
|
|
|
, ("Parencite*", citation "Parencite*" SuppressAuthor False)
|
|
|
|
|
, ("Textcite", citation "Textcite" AuthorInText False)
|
|
|
|
|
, ("Textcites", citation "Textcites" AuthorInText True)
|
|
|
|
|
, ("Cites", citation "Cites" NormalCitation True)
|
|
|
|
|
, ("Autocites", citation "Autocites" NormalCitation True)
|
|
|
|
|
, ("Footcites", citation "Footcites" NormalCitation True)
|
|
|
|
|
, ("Parencites", citation "Parencites" NormalCitation True)
|
|
|
|
|
, ("Supercites", citation "Supercites" NormalCitation True)
|
|
|
|
|
, ("Footcitetexts", inNote <$> citation "Footcitetexts" NormalCitation True)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("citetext", complexNatbibCitation NormalCitation)
|
|
|
|
|
, ("citeauthor", (try (tok *> optional sp *> controlSeq "citetext") *>
|
|
|
|
|
complexNatbibCitation AuthorInText)
|
2012-10-21 23:16:23 -07:00
|
|
|
|
<|> citation "citeauthor" AuthorInText False)
|
2014-04-26 12:14:42 -07:00
|
|
|
|
, ("nocite", mempty <$ (citation "nocite" NormalCitation False >>=
|
|
|
|
|
addMeta "nocite"))
|
2017-03-01 21:05:29 +01:00
|
|
|
|
, ("hypertarget", braced >> tok)
|
2017-04-22 21:57:21 +02:00
|
|
|
|
-- siuntix
|
|
|
|
|
, ("SI", dosiunitx)
|
2017-04-26 12:05:13 +02:00
|
|
|
|
-- hyphenat
|
|
|
|
|
, ("bshyp", lit "\\\173")
|
|
|
|
|
, ("fshyp", lit "/\173")
|
|
|
|
|
, ("dothyp", lit ".\173")
|
|
|
|
|
, ("colonhyp", lit ":\173")
|
|
|
|
|
, ("hyp", lit "-")
|
|
|
|
|
, ("nohyphens", tok)
|
|
|
|
|
, ("textnhtt", ttfamily)
|
|
|
|
|
, ("nhttfamily", ttfamily)
|
2012-02-04 22:28:16 -08:00
|
|
|
|
] ++ map ignoreInlines
|
|
|
|
|
-- these commands will be ignored unless --parse-raw is specified,
|
|
|
|
|
-- in which case they will appear as raw latex blocks:
|
2017-02-25 12:40:53 +01:00
|
|
|
|
[ "index"
|
|
|
|
|
, "hspace"
|
|
|
|
|
, "vspace"
|
2017-03-06 21:46:38 +01:00
|
|
|
|
, "newpage"
|
|
|
|
|
, "clearpage"
|
|
|
|
|
, "pagebreak"
|
2017-02-25 12:40:53 +01:00
|
|
|
|
]
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2017-04-26 12:05:13 +02:00
|
|
|
|
ttfamily :: PandocMonad m => LP m Inlines
|
|
|
|
|
ttfamily = (code . stringify . toList) <$> tok
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
mkImage :: PandocMonad m => [(String, String)] -> String -> LP m Inlines
|
2015-04-02 21:09:08 -07:00
|
|
|
|
mkImage options src = do
|
|
|
|
|
let replaceTextwidth (k,v) = case numUnit v of
|
|
|
|
|
Just (num, "\\textwidth") -> (k, showFl (num * 100) ++ "%")
|
|
|
|
|
_ -> (k, v)
|
|
|
|
|
let kvs = map replaceTextwidth $ filter (\(k,_) -> k `elem` ["width", "height"]) options
|
|
|
|
|
let attr = ("",[], kvs)
|
2014-03-25 23:10:43 -07:00
|
|
|
|
let alt = str "image"
|
2013-02-06 08:36:29 -08:00
|
|
|
|
case takeExtension src of
|
|
|
|
|
"" -> do
|
|
|
|
|
defaultExt <- getOption readerDefaultImageExtension
|
2015-11-19 22:41:12 -08:00
|
|
|
|
return $ imageWith attr (addExtension src defaultExt) "" alt
|
|
|
|
|
_ -> return $ imageWith attr src "" alt
|
2013-02-06 08:36:29 -08:00
|
|
|
|
|
2012-10-21 23:16:23 -07:00
|
|
|
|
inNote :: Inlines -> Inlines
|
|
|
|
|
inNote ils =
|
|
|
|
|
note $ para $ ils <> str "."
|
|
|
|
|
|
2012-01-29 23:54:00 -08:00
|
|
|
|
unescapeURL :: String -> String
|
|
|
|
|
unescapeURL ('\\':x:xs) | isEscapable x = x:unescapeURL xs
|
2015-01-05 14:38:06 +11:00
|
|
|
|
where isEscapable c = c `elem` ("#$%&~_^\\{}" :: String)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
unescapeURL (x:xs) = x:unescapeURL xs
|
|
|
|
|
unescapeURL [] = ""
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
enquote :: PandocMonad m => LP m Inlines
|
2012-10-15 20:15:34 -07:00
|
|
|
|
enquote = do
|
|
|
|
|
skipopts
|
|
|
|
|
context <- stateQuoteContext <$> getState
|
|
|
|
|
if context == InDoubleQuote
|
|
|
|
|
then singleQuoted <$> withQuoteContext InSingleQuote tok
|
|
|
|
|
else doubleQuoted <$> withQuoteContext InDoubleQuote tok
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
doverb :: PandocMonad m => LP m Inlines
|
2012-01-29 23:54:00 -08:00
|
|
|
|
doverb = do
|
|
|
|
|
marker <- anyChar
|
|
|
|
|
code <$> manyTill (satisfy (/='\n')) (char marker)
|
|
|
|
|
|
2017-03-29 14:49:46 +02:00
|
|
|
|
dolstinline :: PandocMonad m => LP m Inlines
|
|
|
|
|
dolstinline = do
|
|
|
|
|
options <- option [] keyvals
|
|
|
|
|
let classes = maybeToList $ lookup "language" options >>= fromListingsLanguage
|
|
|
|
|
marker <- char '{' <|> anyChar
|
|
|
|
|
codeWith ("",classes,[]) <$> manyTill (satisfy (/='\n')) (char '}' <|> char marker)
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
doLHSverb :: PandocMonad m => LP m Inlines
|
2012-01-29 23:54:00 -08:00
|
|
|
|
doLHSverb = codeWith ("",["haskell"],[]) <$> manyTill (satisfy (/='\n')) (char '|')
|
|
|
|
|
|
2017-04-22 21:57:21 +02:00
|
|
|
|
-- converts e.g. \SI{1}[\$]{} to "$ 1" or \SI{1}{\euro} to "1 €"
|
|
|
|
|
dosiunitx :: PandocMonad m => LP m Inlines
|
|
|
|
|
dosiunitx = do
|
|
|
|
|
skipopts
|
|
|
|
|
value <- tok
|
|
|
|
|
valueprefix <- option "" $ char '[' >> (mconcat <$> manyTill tok (char ']'))
|
|
|
|
|
unit <- tok
|
|
|
|
|
let emptyOr160 "" = ""
|
|
|
|
|
emptyOr160 _ = "\160"
|
|
|
|
|
return . mconcat $ [valueprefix,
|
|
|
|
|
emptyOr160 valueprefix,
|
|
|
|
|
value,
|
|
|
|
|
emptyOr160 unit,
|
|
|
|
|
unit]
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
lit :: String -> LP m Inlines
|
2012-01-29 23:54:00 -08:00
|
|
|
|
lit = pure . str
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
accent :: (Char -> String) -> Inlines -> LP m Inlines
|
2012-01-29 23:54:00 -08:00
|
|
|
|
accent f ils =
|
|
|
|
|
case toList ils of
|
2015-04-12 09:47:13 +03:00
|
|
|
|
(Str (x:xs) : ys) -> return $ fromList (Str (f x ++ xs) : ys)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
[] -> mzero
|
|
|
|
|
_ -> return ils
|
|
|
|
|
|
2013-08-27 20:12:21 -07:00
|
|
|
|
grave :: Char -> String
|
|
|
|
|
grave 'A' = "À"
|
|
|
|
|
grave 'E' = "È"
|
|
|
|
|
grave 'I' = "Ì"
|
|
|
|
|
grave 'O' = "Ò"
|
|
|
|
|
grave 'U' = "Ù"
|
|
|
|
|
grave 'a' = "à"
|
|
|
|
|
grave 'e' = "è"
|
|
|
|
|
grave 'i' = "ì"
|
|
|
|
|
grave 'o' = "ò"
|
|
|
|
|
grave 'u' = "ù"
|
|
|
|
|
grave c = [c]
|
|
|
|
|
|
|
|
|
|
acute :: Char -> String
|
|
|
|
|
acute 'A' = "Á"
|
|
|
|
|
acute 'E' = "É"
|
|
|
|
|
acute 'I' = "Í"
|
|
|
|
|
acute 'O' = "Ó"
|
|
|
|
|
acute 'U' = "Ú"
|
|
|
|
|
acute 'Y' = "Ý"
|
|
|
|
|
acute 'a' = "á"
|
|
|
|
|
acute 'e' = "é"
|
|
|
|
|
acute 'i' = "í"
|
|
|
|
|
acute 'o' = "ó"
|
|
|
|
|
acute 'u' = "ú"
|
|
|
|
|
acute 'y' = "ý"
|
|
|
|
|
acute 'C' = "Ć"
|
|
|
|
|
acute 'c' = "ć"
|
|
|
|
|
acute 'L' = "Ĺ"
|
|
|
|
|
acute 'l' = "ĺ"
|
|
|
|
|
acute 'N' = "Ń"
|
|
|
|
|
acute 'n' = "ń"
|
|
|
|
|
acute 'R' = "Ŕ"
|
|
|
|
|
acute 'r' = "ŕ"
|
|
|
|
|
acute 'S' = "Ś"
|
|
|
|
|
acute 's' = "ś"
|
|
|
|
|
acute 'Z' = "Ź"
|
|
|
|
|
acute 'z' = "ź"
|
|
|
|
|
acute c = [c]
|
|
|
|
|
|
|
|
|
|
circ :: Char -> String
|
|
|
|
|
circ 'A' = "Â"
|
|
|
|
|
circ 'E' = "Ê"
|
|
|
|
|
circ 'I' = "Î"
|
|
|
|
|
circ 'O' = "Ô"
|
|
|
|
|
circ 'U' = "Û"
|
|
|
|
|
circ 'a' = "â"
|
|
|
|
|
circ 'e' = "ê"
|
|
|
|
|
circ 'i' = "î"
|
|
|
|
|
circ 'o' = "ô"
|
|
|
|
|
circ 'u' = "û"
|
|
|
|
|
circ 'C' = "Ĉ"
|
|
|
|
|
circ 'c' = "ĉ"
|
|
|
|
|
circ 'G' = "Ĝ"
|
|
|
|
|
circ 'g' = "ĝ"
|
|
|
|
|
circ 'H' = "Ĥ"
|
|
|
|
|
circ 'h' = "ĥ"
|
|
|
|
|
circ 'J' = "Ĵ"
|
|
|
|
|
circ 'j' = "ĵ"
|
|
|
|
|
circ 'S' = "Ŝ"
|
|
|
|
|
circ 's' = "ŝ"
|
|
|
|
|
circ 'W' = "Ŵ"
|
|
|
|
|
circ 'w' = "ŵ"
|
|
|
|
|
circ 'Y' = "Ŷ"
|
|
|
|
|
circ 'y' = "ŷ"
|
|
|
|
|
circ c = [c]
|
|
|
|
|
|
|
|
|
|
tilde :: Char -> String
|
|
|
|
|
tilde 'A' = "Ã"
|
|
|
|
|
tilde 'a' = "ã"
|
|
|
|
|
tilde 'O' = "Õ"
|
|
|
|
|
tilde 'o' = "õ"
|
|
|
|
|
tilde 'I' = "Ĩ"
|
|
|
|
|
tilde 'i' = "ĩ"
|
|
|
|
|
tilde 'U' = "Ũ"
|
|
|
|
|
tilde 'u' = "ũ"
|
|
|
|
|
tilde 'N' = "Ñ"
|
|
|
|
|
tilde 'n' = "ñ"
|
|
|
|
|
tilde c = [c]
|
|
|
|
|
|
|
|
|
|
umlaut :: Char -> String
|
|
|
|
|
umlaut 'A' = "Ä"
|
|
|
|
|
umlaut 'E' = "Ë"
|
|
|
|
|
umlaut 'I' = "Ï"
|
|
|
|
|
umlaut 'O' = "Ö"
|
|
|
|
|
umlaut 'U' = "Ü"
|
|
|
|
|
umlaut 'a' = "ä"
|
|
|
|
|
umlaut 'e' = "ë"
|
|
|
|
|
umlaut 'i' = "ï"
|
|
|
|
|
umlaut 'o' = "ö"
|
|
|
|
|
umlaut 'u' = "ü"
|
|
|
|
|
umlaut c = [c]
|
|
|
|
|
|
2016-11-01 10:17:15 +01:00
|
|
|
|
hungarumlaut :: Char -> String
|
|
|
|
|
hungarumlaut 'A' = "A̋"
|
|
|
|
|
hungarumlaut 'E' = "E̋"
|
|
|
|
|
hungarumlaut 'I' = "I̋"
|
|
|
|
|
hungarumlaut 'O' = "Ő"
|
|
|
|
|
hungarumlaut 'U' = "Ű"
|
|
|
|
|
hungarumlaut 'Y' = "ӳ"
|
|
|
|
|
hungarumlaut 'a' = "a̋"
|
|
|
|
|
hungarumlaut 'e' = "e̋"
|
|
|
|
|
hungarumlaut 'i' = "i̋"
|
|
|
|
|
hungarumlaut 'o' = "ő"
|
|
|
|
|
hungarumlaut 'u' = "ű"
|
|
|
|
|
hungarumlaut 'y' = "ӳ"
|
|
|
|
|
hungarumlaut c = [c]
|
|
|
|
|
|
2013-08-27 20:12:21 -07:00
|
|
|
|
dot :: Char -> String
|
|
|
|
|
dot 'C' = "Ċ"
|
|
|
|
|
dot 'c' = "ċ"
|
|
|
|
|
dot 'E' = "Ė"
|
|
|
|
|
dot 'e' = "ė"
|
|
|
|
|
dot 'G' = "Ġ"
|
|
|
|
|
dot 'g' = "ġ"
|
|
|
|
|
dot 'I' = "İ"
|
|
|
|
|
dot 'Z' = "Ż"
|
|
|
|
|
dot 'z' = "ż"
|
|
|
|
|
dot c = [c]
|
|
|
|
|
|
|
|
|
|
macron :: Char -> String
|
|
|
|
|
macron 'A' = "Ā"
|
|
|
|
|
macron 'E' = "Ē"
|
|
|
|
|
macron 'I' = "Ī"
|
|
|
|
|
macron 'O' = "Ō"
|
|
|
|
|
macron 'U' = "Ū"
|
|
|
|
|
macron 'a' = "ā"
|
|
|
|
|
macron 'e' = "ē"
|
|
|
|
|
macron 'i' = "ī"
|
|
|
|
|
macron 'o' = "ō"
|
|
|
|
|
macron 'u' = "ū"
|
|
|
|
|
macron c = [c]
|
|
|
|
|
|
|
|
|
|
cedilla :: Char -> String
|
|
|
|
|
cedilla 'c' = "ç"
|
|
|
|
|
cedilla 'C' = "Ç"
|
|
|
|
|
cedilla 's' = "ş"
|
|
|
|
|
cedilla 'S' = "Ş"
|
|
|
|
|
cedilla 't' = "ţ"
|
|
|
|
|
cedilla 'T' = "Ţ"
|
|
|
|
|
cedilla 'e' = "ȩ"
|
|
|
|
|
cedilla 'E' = "Ȩ"
|
|
|
|
|
cedilla 'h' = "ḩ"
|
|
|
|
|
cedilla 'H' = "Ḩ"
|
|
|
|
|
cedilla 'o' = "o̧"
|
|
|
|
|
cedilla 'O' = "O̧"
|
|
|
|
|
cedilla c = [c]
|
|
|
|
|
|
|
|
|
|
hacek :: Char -> String
|
|
|
|
|
hacek 'A' = "Ǎ"
|
|
|
|
|
hacek 'a' = "ǎ"
|
|
|
|
|
hacek 'C' = "Č"
|
|
|
|
|
hacek 'c' = "č"
|
|
|
|
|
hacek 'D' = "Ď"
|
|
|
|
|
hacek 'd' = "ď"
|
|
|
|
|
hacek 'E' = "Ě"
|
|
|
|
|
hacek 'e' = "ě"
|
|
|
|
|
hacek 'G' = "Ǧ"
|
|
|
|
|
hacek 'g' = "ǧ"
|
|
|
|
|
hacek 'H' = "Ȟ"
|
|
|
|
|
hacek 'h' = "ȟ"
|
|
|
|
|
hacek 'I' = "Ǐ"
|
|
|
|
|
hacek 'i' = "ǐ"
|
|
|
|
|
hacek 'j' = "ǰ"
|
|
|
|
|
hacek 'K' = "Ǩ"
|
|
|
|
|
hacek 'k' = "ǩ"
|
|
|
|
|
hacek 'L' = "Ľ"
|
|
|
|
|
hacek 'l' = "ľ"
|
|
|
|
|
hacek 'N' = "Ň"
|
|
|
|
|
hacek 'n' = "ň"
|
|
|
|
|
hacek 'O' = "Ǒ"
|
|
|
|
|
hacek 'o' = "ǒ"
|
|
|
|
|
hacek 'R' = "Ř"
|
|
|
|
|
hacek 'r' = "ř"
|
|
|
|
|
hacek 'S' = "Š"
|
|
|
|
|
hacek 's' = "š"
|
|
|
|
|
hacek 'T' = "Ť"
|
|
|
|
|
hacek 't' = "ť"
|
|
|
|
|
hacek 'U' = "Ǔ"
|
|
|
|
|
hacek 'u' = "ǔ"
|
|
|
|
|
hacek 'Z' = "Ž"
|
|
|
|
|
hacek 'z' = "ž"
|
|
|
|
|
hacek c = [c]
|
|
|
|
|
|
|
|
|
|
breve :: Char -> String
|
|
|
|
|
breve 'A' = "Ă"
|
|
|
|
|
breve 'a' = "ă"
|
|
|
|
|
breve 'E' = "Ĕ"
|
|
|
|
|
breve 'e' = "ĕ"
|
|
|
|
|
breve 'G' = "Ğ"
|
|
|
|
|
breve 'g' = "ğ"
|
|
|
|
|
breve 'I' = "Ĭ"
|
|
|
|
|
breve 'i' = "ĭ"
|
|
|
|
|
breve 'O' = "Ŏ"
|
|
|
|
|
breve 'o' = "ŏ"
|
|
|
|
|
breve 'U' = "Ŭ"
|
|
|
|
|
breve 'u' = "ŭ"
|
|
|
|
|
breve c = [c]
|
2013-08-16 10:03:54 +10:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
tok :: PandocMonad m => LP m Inlines
|
2015-04-12 09:47:13 +03:00
|
|
|
|
tok = try $ grouped inline <|> inlineCommand <|> str <$> count 1 inlineChar
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
opt :: PandocMonad m => LP m Inlines
|
2015-10-09 14:39:42 -07:00
|
|
|
|
opt = bracketed inline
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
rawopt :: PandocMonad m => LP m String
|
2016-07-20 11:18:24 -07:00
|
|
|
|
rawopt = do
|
2016-10-31 22:04:22 +01:00
|
|
|
|
contents <- bracketed (many1 (noneOf "[]") <|> try (string "\\]") <|>
|
|
|
|
|
try (string "\\[") <|> rawopt)
|
2016-07-20 11:18:24 -07:00
|
|
|
|
optional sp
|
|
|
|
|
return $ "[" ++ contents ++ "]"
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
skipopts :: PandocMonad m => LP m ()
|
2016-07-20 11:18:24 -07:00
|
|
|
|
skipopts = skipMany rawopt
|
2012-02-09 17:45:40 -08:00
|
|
|
|
|
2016-11-20 21:17:41 +01:00
|
|
|
|
-- opts in angle brackets are used in beamer
|
2016-11-28 17:13:46 -05:00
|
|
|
|
rawangle :: PandocMonad m => LP m ()
|
2016-11-20 21:17:41 +01:00
|
|
|
|
rawangle = try $ do
|
|
|
|
|
char '<'
|
2017-03-24 16:31:34 +01:00
|
|
|
|
skipMany (noneOf ">")
|
2016-11-20 21:17:41 +01:00
|
|
|
|
char '>'
|
|
|
|
|
return ()
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
skipangles :: PandocMonad m => LP m ()
|
2016-11-20 21:17:41 +01:00
|
|
|
|
skipangles = skipMany rawangle
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
inlineText :: PandocMonad m => LP m Inlines
|
2012-01-29 23:54:00 -08:00
|
|
|
|
inlineText = str <$> many1 inlineChar
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
inlineChar :: PandocMonad m => LP m Char
|
2015-06-29 10:20:08 -07:00
|
|
|
|
inlineChar = noneOf "\\$%&~#{}^'`\"‘’“”-[] \t\n"
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
environment :: PandocMonad m => LP m Blocks
|
2012-01-29 23:54:00 -08:00
|
|
|
|
environment = do
|
|
|
|
|
controlSeq "begin"
|
|
|
|
|
name <- braced
|
2015-04-12 09:47:13 +03:00
|
|
|
|
M.findWithDefault mzero name environments
|
|
|
|
|
<|> rawEnv name
|
2012-02-04 12:27:24 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
inlineEnvironment :: PandocMonad m => LP m Inlines
|
2014-12-16 12:27:04 -08:00
|
|
|
|
inlineEnvironment = try $ do
|
|
|
|
|
controlSeq "begin"
|
|
|
|
|
name <- braced
|
2015-04-12 09:47:13 +03:00
|
|
|
|
M.findWithDefault mzero name inlineEnvironments
|
2014-12-16 12:27:04 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
rawEnv :: PandocMonad m => String -> LP m Blocks
|
2012-02-04 12:27:24 -08:00
|
|
|
|
rawEnv name = do
|
2017-02-06 23:33:23 +01:00
|
|
|
|
exts <- getOption readerExtensions
|
2017-02-10 10:00:23 +01:00
|
|
|
|
let parseRaw = extensionEnabled Ext_raw_tex exts
|
2016-07-20 11:18:24 -07:00
|
|
|
|
rawOptions <- mconcat <$> many rawopt
|
2017-02-10 10:00:23 +01:00
|
|
|
|
let beginCommand = "\\begin{" ++ name ++ "}" ++ rawOptions
|
2017-03-10 09:46:32 +01:00
|
|
|
|
pos1 <- getPosition
|
2017-02-10 10:00:23 +01:00
|
|
|
|
(bs, raw) <- withRaw $ env name blocks
|
2017-03-10 09:46:32 +01:00
|
|
|
|
raw' <- applyMacros' $ beginCommand ++ raw
|
|
|
|
|
if raw' /= beginCommand ++ raw
|
|
|
|
|
then parseFromString blocks raw'
|
|
|
|
|
else if parseRaw
|
|
|
|
|
then return $ rawBlock "latex" $ beginCommand ++ raw'
|
|
|
|
|
else do
|
|
|
|
|
unless parseRaw $ do
|
|
|
|
|
report $ SkippedContent beginCommand pos1
|
|
|
|
|
pos2 <- getPosition
|
|
|
|
|
report $ SkippedContent ("\\end{" ++ name ++ "}") pos2
|
|
|
|
|
return bs
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2014-05-03 15:15:04 -07:00
|
|
|
|
----
|
|
|
|
|
|
2015-01-22 23:17:25 -08:00
|
|
|
|
maybeAddExtension :: String -> FilePath -> FilePath
|
|
|
|
|
maybeAddExtension ext fp =
|
|
|
|
|
if null (takeExtension fp)
|
|
|
|
|
then addExtension fp ext
|
|
|
|
|
else fp
|
|
|
|
|
|
2016-12-03 21:55:31 +01:00
|
|
|
|
include :: PandocMonad m => LP m Blocks
|
|
|
|
|
include = do
|
2014-05-03 18:34:23 -07:00
|
|
|
|
fs' <- try $ do
|
2014-05-03 15:15:04 -07:00
|
|
|
|
char '\\'
|
2014-05-03 18:34:23 -07:00
|
|
|
|
name <- try (string "include")
|
|
|
|
|
<|> try (string "input")
|
2017-03-27 21:20:27 +02:00
|
|
|
|
<|> try (string "subfile")
|
2014-05-03 18:34:23 -07:00
|
|
|
|
<|> string "usepackage"
|
|
|
|
|
-- skip options
|
2015-04-12 09:47:13 +03:00
|
|
|
|
skipMany $ try $ char '[' *> manyTill anyChar (char ']')
|
2017-03-05 11:17:03 +01:00
|
|
|
|
fs <- (map trim . splitBy (==',')) <$> braced
|
2014-05-03 18:34:23 -07:00
|
|
|
|
return $ if name == "usepackage"
|
2015-01-22 23:17:25 -08:00
|
|
|
|
then map (maybeAddExtension ".sty") fs
|
|
|
|
|
else map (maybeAddExtension ".tex") fs
|
2017-02-07 21:42:35 +01:00
|
|
|
|
dirs <- (splitBy (==':') . fromMaybe ".") <$> lookupEnv "TEXINPUTS"
|
2017-02-07 22:33:05 +01:00
|
|
|
|
mconcat <$> mapM (insertIncludedFile blocks dirs) fs'
|
2016-12-03 21:55:31 +01:00
|
|
|
|
|
2017-02-08 00:07:53 +01:00
|
|
|
|
inputListing :: PandocMonad m => LP m Blocks
|
|
|
|
|
inputListing = do
|
2017-02-10 23:59:47 +01:00
|
|
|
|
pos <- getPosition
|
2017-02-08 00:07:53 +01:00
|
|
|
|
options <- option [] keyvals
|
|
|
|
|
f <- filter (/='"') <$> braced
|
|
|
|
|
dirs <- (splitBy (==':') . fromMaybe ".") <$> lookupEnv "TEXINPUTS"
|
2017-02-10 23:59:47 +01:00
|
|
|
|
mbCode <- readFileFromDirs dirs f
|
|
|
|
|
codeLines <- case mbCode of
|
|
|
|
|
Just s -> return $ lines s
|
|
|
|
|
Nothing -> do
|
|
|
|
|
report $ CouldNotLoadIncludeFile f pos
|
|
|
|
|
return []
|
2017-02-08 00:07:53 +01:00
|
|
|
|
let (ident,classes,kvs) = parseListingsOptions options
|
|
|
|
|
let language = case lookup "language" options >>= fromListingsLanguage of
|
|
|
|
|
Just l -> [l]
|
|
|
|
|
Nothing -> take 1 $ languagesByExtension (takeExtension f)
|
|
|
|
|
let firstline = fromMaybe 1 $ lookup "firstline" options >>= safeRead
|
|
|
|
|
let lastline = fromMaybe (length codeLines) $
|
|
|
|
|
lookup "lastline" options >>= safeRead
|
|
|
|
|
let codeContents = intercalate "\n" $ take (1 + lastline - firstline) $
|
|
|
|
|
drop (firstline - 1) codeLines
|
|
|
|
|
return $ codeBlockWith (ident,ordNub (classes ++ language),kvs) codeContents
|
|
|
|
|
|
|
|
|
|
parseListingsOptions :: [(String, String)] -> Attr
|
|
|
|
|
parseListingsOptions options =
|
|
|
|
|
let kvs = [ (if k == "firstnumber"
|
|
|
|
|
then "startFrom"
|
|
|
|
|
else k, v) | (k,v) <- options ]
|
|
|
|
|
classes = [ "numberLines" |
|
|
|
|
|
lookup "numbers" options == Just "left" ]
|
|
|
|
|
++ maybeToList (lookup "language" options
|
|
|
|
|
>>= fromListingsLanguage)
|
|
|
|
|
in (fromMaybe "" (lookup "label" options), classes, kvs)
|
|
|
|
|
|
2014-05-03 15:15:04 -07:00
|
|
|
|
----
|
2012-02-04 22:28:16 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
keyval :: PandocMonad m => LP m (String, String)
|
2013-03-04 09:50:11 -08:00
|
|
|
|
keyval = try $ do
|
|
|
|
|
key <- many1 alphaNum
|
2015-04-02 21:09:08 -07:00
|
|
|
|
val <- option "" $ char '=' >> many1 (alphaNum <|> char '.' <|> char '\\')
|
2013-03-04 09:50:11 -08:00
|
|
|
|
skipMany spaceChar
|
|
|
|
|
optional (char ',')
|
|
|
|
|
skipMany spaceChar
|
|
|
|
|
return (key, val)
|
|
|
|
|
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
keyvals :: PandocMonad m => LP m [(String, String)]
|
2013-03-04 09:50:11 -08:00
|
|
|
|
keyvals = try $ char '[' *> manyTill keyval (char ']')
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
alltt :: PandocMonad m => String -> LP m Blocks
|
2013-08-10 18:45:00 -07:00
|
|
|
|
alltt t = walk strToCode <$> parseFromString blocks
|
2013-06-27 18:54:31 -07:00
|
|
|
|
(substitute " " "\\ " $ substitute "%" "\\%" $
|
2015-04-12 09:47:13 +03:00
|
|
|
|
intercalate "\\\\\n" $ lines t)
|
2013-06-27 18:54:31 -07:00
|
|
|
|
where strToCode (Str s) = Code nullAttr s
|
|
|
|
|
strToCode x = x
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
rawLaTeXBlock :: PandocMonad m => LP m String
|
2012-09-22 13:00:59 -07:00
|
|
|
|
rawLaTeXBlock = snd <$> try (withRaw (environment <|> blockCommand))
|
2010-07-13 19:18:58 -07:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
rawLaTeXInline :: PandocMonad m => LP m Inline
|
2012-01-29 23:54:00 -08:00
|
|
|
|
rawLaTeXInline = do
|
2017-03-07 14:57:11 +01:00
|
|
|
|
raw <- (snd <$> withRaw inlineCommand)
|
|
|
|
|
<|> (snd <$> withRaw inlineEnvironment)
|
|
|
|
|
<|> (snd <$> withRaw blockCommand)
|
2012-10-11 21:21:09 -07:00
|
|
|
|
RawInline "latex" <$> applyMacros' raw
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
addImageCaption :: PandocMonad m => Blocks -> LP m Blocks
|
2014-03-25 23:10:43 -07:00
|
|
|
|
addImageCaption = walkM go
|
2017-04-24 23:39:14 +02:00
|
|
|
|
where go (Image attr alt (src,tit))
|
|
|
|
|
| not ("fig:" `isPrefixOf` tit) = do
|
2014-03-25 23:10:43 -07:00
|
|
|
|
mbcapt <- stateCaption <$> getState
|
2015-04-12 09:47:13 +03:00
|
|
|
|
return $ case mbcapt of
|
2017-04-24 23:39:14 +02:00
|
|
|
|
Just ils -> Image attr (toList ils) (src, "fig:" ++ tit)
|
2015-04-02 21:09:08 -07:00
|
|
|
|
Nothing -> Image attr alt (src,tit)
|
2014-03-25 23:10:43 -07:00
|
|
|
|
go x = return x
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
addTableCaption :: PandocMonad m => Blocks -> LP m Blocks
|
2014-03-25 23:10:43 -07:00
|
|
|
|
addTableCaption = walkM go
|
|
|
|
|
where go (Table c als ws hs rs) = do
|
|
|
|
|
mbcapt <- stateCaption <$> getState
|
2015-04-12 09:47:13 +03:00
|
|
|
|
return $ case mbcapt of
|
|
|
|
|
Just ils -> Table (toList ils) als ws hs rs
|
|
|
|
|
Nothing -> Table c als ws hs rs
|
2014-03-25 23:10:43 -07:00
|
|
|
|
go x = return x
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
environments :: PandocMonad m => M.Map String (LP m Blocks)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
environments = M.fromList
|
2012-02-05 08:46:04 -08:00
|
|
|
|
[ ("document", env "document" blocks <* skipMany anyChar)
|
2015-07-23 09:31:46 -07:00
|
|
|
|
, ("abstract", mempty <$ (env "abstract" blocks >>= addMeta "abstract"))
|
2015-04-12 09:47:13 +03:00
|
|
|
|
, ("letter", env "letter" letterContents)
|
2016-11-19 21:43:46 +01:00
|
|
|
|
, ("minipage", env "minipage" $
|
2016-11-19 22:45:36 +01:00
|
|
|
|
skipopts *> spaces' *> optional braced *> spaces' *> blocks)
|
2017-04-24 23:39:14 +02:00
|
|
|
|
, ("figure", env "figure" $ skipopts *> figure)
|
|
|
|
|
, ("subfigure", env "subfigure" $ skipopts *> tok *> figure)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("center", env "center" blocks)
|
2015-10-15 23:15:40 -07:00
|
|
|
|
, ("longtable", env "longtable" $
|
2016-11-19 21:36:16 +01:00
|
|
|
|
resetCaption *> simpTable False >>= addTableCaption)
|
2014-03-25 23:10:43 -07:00
|
|
|
|
, ("table", env "table" $
|
|
|
|
|
resetCaption *> skipopts *> blocks >>= addTableCaption)
|
2015-01-01 08:46:45 -08:00
|
|
|
|
, ("tabular*", env "tabular" $ simpTable True)
|
2017-05-03 12:16:48 +02:00
|
|
|
|
, ("tabularx", env "tabularx" $ simpTable True)
|
2015-01-01 08:46:45 -08:00
|
|
|
|
, ("tabular", env "tabular" $ simpTable False)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("quote", blockQuote <$> env "quote" blocks)
|
|
|
|
|
, ("quotation", blockQuote <$> env "quotation" blocks)
|
2012-02-08 14:03:55 -08:00
|
|
|
|
, ("verse", blockQuote <$> env "verse" blocks)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
, ("itemize", bulletList <$> listenv "itemize" (many item))
|
|
|
|
|
, ("description", definitionList <$> listenv "description" (many descItem))
|
2015-04-12 09:47:13 +03:00
|
|
|
|
, ("enumerate", orderedList')
|
2013-06-27 18:54:31 -07:00
|
|
|
|
, ("alltt", alltt =<< verbEnv "alltt")
|
2012-08-08 23:18:19 -07:00
|
|
|
|
, ("code", guardEnabled Ext_literate_haskell *>
|
2012-02-04 12:27:37 -08:00
|
|
|
|
(codeBlockWith ("",["sourceCode","literate","haskell"],[]) <$>
|
|
|
|
|
verbEnv "code"))
|
2015-11-08 02:24:25 +09:00
|
|
|
|
, ("comment", mempty <$ verbEnv "comment")
|
2015-04-12 09:47:13 +03:00
|
|
|
|
, ("verbatim", codeBlock <$> verbEnv "verbatim")
|
2016-11-02 12:05:56 +01:00
|
|
|
|
, ("Verbatim", fancyverbEnv "Verbatim")
|
|
|
|
|
, ("BVerbatim", fancyverbEnv "BVerbatim")
|
2017-02-08 00:07:53 +01:00
|
|
|
|
, ("lstlisting", do attr <- parseListingsOptions <$> option [] keyvals
|
2015-04-12 09:47:13 +03:00
|
|
|
|
codeBlockWith attr <$> verbEnv "lstlisting")
|
2013-03-06 09:58:47 -08:00
|
|
|
|
, ("minted", do options <- option [] keyvals
|
|
|
|
|
lang <- grouped (many1 $ satisfy (/='}'))
|
|
|
|
|
let kvs = [ (if k == "firstnumber"
|
|
|
|
|
then "startFrom"
|
|
|
|
|
else k, v) | (k,v) <- options ]
|
|
|
|
|
let classes = [ lang | not (null lang) ] ++
|
|
|
|
|
[ "numberLines" |
|
|
|
|
|
lookup "linenos" options == Just "true" ]
|
|
|
|
|
let attr = ("",classes,kvs)
|
2015-04-12 09:47:13 +03:00
|
|
|
|
codeBlockWith attr <$> verbEnv "minted")
|
2012-09-06 16:27:01 -07:00
|
|
|
|
, ("obeylines", parseFromString
|
|
|
|
|
(para . trimInlines . mconcat <$> many inline) =<<
|
|
|
|
|
intercalate "\\\\\n" . lines <$> verbEnv "obeylines")
|
2014-12-16 12:27:04 -08:00
|
|
|
|
, ("displaymath", mathEnv para Nothing "displaymath")
|
|
|
|
|
, ("equation", mathEnv para Nothing "equation")
|
|
|
|
|
, ("equation*", mathEnv para Nothing "equation*")
|
|
|
|
|
, ("gather", mathEnv para (Just "gathered") "gather")
|
|
|
|
|
, ("gather*", mathEnv para (Just "gathered") "gather*")
|
|
|
|
|
, ("multline", mathEnv para (Just "gathered") "multline")
|
|
|
|
|
, ("multline*", mathEnv para (Just "gathered") "multline*")
|
|
|
|
|
, ("eqnarray", mathEnv para (Just "aligned") "eqnarray")
|
|
|
|
|
, ("eqnarray*", mathEnv para (Just "aligned") "eqnarray*")
|
|
|
|
|
, ("align", mathEnv para (Just "aligned") "align")
|
|
|
|
|
, ("align*", mathEnv para (Just "aligned") "align*")
|
|
|
|
|
, ("alignat", mathEnv para (Just "aligned") "alignat")
|
|
|
|
|
, ("alignat*", mathEnv para (Just "aligned") "alignat*")
|
2012-01-29 23:54:00 -08:00
|
|
|
|
]
|
|
|
|
|
|
2017-04-24 23:39:14 +02:00
|
|
|
|
figure :: PandocMonad m => LP m Blocks
|
|
|
|
|
figure = try $ do
|
|
|
|
|
resetCaption
|
|
|
|
|
blocks >>= addImageCaption
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
letterContents :: PandocMonad m => LP m Blocks
|
2015-04-12 09:47:13 +03:00
|
|
|
|
letterContents = do
|
2012-02-04 20:02:00 -08:00
|
|
|
|
bs <- blocks
|
|
|
|
|
st <- getState
|
|
|
|
|
-- add signature (author) and address (title)
|
2013-05-10 22:53:35 -07:00
|
|
|
|
let addr = case lookupMeta "address" (stateMeta st) of
|
|
|
|
|
Just (MetaBlocks [Plain xs]) ->
|
|
|
|
|
para $ trimInlines $ fromList xs
|
|
|
|
|
_ -> mempty
|
2012-02-04 22:28:16 -08:00
|
|
|
|
return $ addr <> bs -- sig added by \closing
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
closing :: PandocMonad m => LP m Blocks
|
2012-02-04 22:28:16 -08:00
|
|
|
|
closing = do
|
|
|
|
|
contents <- tok
|
|
|
|
|
st <- getState
|
2013-05-10 22:53:35 -07:00
|
|
|
|
let extractInlines (MetaBlocks [Plain ys]) = ys
|
|
|
|
|
extractInlines (MetaBlocks [Para ys ]) = ys
|
2017-03-04 13:03:41 +01:00
|
|
|
|
extractInlines _ = []
|
2013-05-10 22:53:35 -07:00
|
|
|
|
let sigs = case lookupMeta "author" (stateMeta st) of
|
|
|
|
|
Just (MetaList xs) ->
|
|
|
|
|
para $ trimInlines $ fromList $
|
|
|
|
|
intercalate [LineBreak] $ map extractInlines xs
|
|
|
|
|
_ -> mempty
|
2012-02-04 22:28:16 -08:00
|
|
|
|
return $ para (trimInlines contents) <> sigs
|
2012-02-04 20:02:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
item :: PandocMonad m => LP m Blocks
|
2012-02-09 17:45:40 -08:00
|
|
|
|
item = blocks *> controlSeq "item" *> skipopts *> blocks
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
looseItem :: PandocMonad m => LP m Blocks
|
2015-04-12 09:47:13 +03:00
|
|
|
|
looseItem = do
|
2012-01-29 23:54:00 -08:00
|
|
|
|
ctx <- stateParserContext `fmap` getState
|
|
|
|
|
if ctx == ListItemState
|
|
|
|
|
then mzero
|
|
|
|
|
else return mempty
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
descItem :: PandocMonad m => LP m (Inlines, [Blocks])
|
2012-01-29 23:54:00 -08:00
|
|
|
|
descItem = do
|
|
|
|
|
blocks -- skip blocks before item
|
|
|
|
|
controlSeq "item"
|
|
|
|
|
optional sp
|
|
|
|
|
ils <- opt
|
|
|
|
|
bs <- blocks
|
|
|
|
|
return (ils, [bs])
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
env :: PandocMonad m => String -> LP m a -> LP m a
|
2012-09-09 19:23:55 -07:00
|
|
|
|
env name p = p <*
|
|
|
|
|
(try (controlSeq "end" *> braced >>= guard . (== name))
|
|
|
|
|
<?> ("\\end{" ++ name ++ "}"))
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
listenv :: PandocMonad m => String -> LP m a -> LP m a
|
2012-01-29 23:54:00 -08:00
|
|
|
|
listenv name p = try $ do
|
|
|
|
|
oldCtx <- stateParserContext `fmap` getState
|
|
|
|
|
updateState $ \st -> st{ stateParserContext = ListItemState }
|
|
|
|
|
res <- env name p
|
|
|
|
|
updateState $ \st -> st{ stateParserContext = oldCtx }
|
|
|
|
|
return res
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
mathEnv :: PandocMonad m => (Inlines -> a) -> Maybe String -> String -> LP m a
|
2014-12-16 12:27:04 -08:00
|
|
|
|
mathEnv f innerEnv name = f <$> mathDisplay (inner <$> verbEnv name)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
where inner x = case innerEnv of
|
|
|
|
|
Nothing -> x
|
|
|
|
|
Just y -> "\\begin{" ++ y ++ "}\n" ++ x ++
|
|
|
|
|
"\\end{" ++ y ++ "}"
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
verbEnv :: PandocMonad m => String -> LP m String
|
2012-01-29 23:54:00 -08:00
|
|
|
|
verbEnv name = do
|
2012-02-09 17:45:40 -08:00
|
|
|
|
skipopts
|
2012-01-29 23:54:00 -08:00
|
|
|
|
optional blankline
|
|
|
|
|
let endEnv = try $ controlSeq "end" *> braced >>= guard . (== name)
|
|
|
|
|
res <- manyTill anyChar endEnv
|
|
|
|
|
return $ stripTrailingNewlines res
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
fancyverbEnv :: PandocMonad m => String -> LP m Blocks
|
2016-11-02 12:05:56 +01:00
|
|
|
|
fancyverbEnv name = do
|
|
|
|
|
options <- option [] keyvals
|
|
|
|
|
let kvs = [ (if k == "firstnumber"
|
|
|
|
|
then "startFrom"
|
|
|
|
|
else k, v) | (k,v) <- options ]
|
|
|
|
|
let classes = [ "numberLines" |
|
|
|
|
|
lookup "numbers" options == Just "left" ]
|
|
|
|
|
let attr = ("",classes,kvs)
|
|
|
|
|
codeBlockWith attr <$> verbEnv name
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
orderedList' :: PandocMonad m => LP m Blocks
|
2015-04-12 09:47:13 +03:00
|
|
|
|
orderedList' = do
|
2012-01-29 23:54:00 -08:00
|
|
|
|
optional sp
|
|
|
|
|
(_, style, delim) <- option (1, DefaultStyle, DefaultDelim) $
|
|
|
|
|
try $ char '[' *> anyOrderedListMarker <* char ']'
|
2010-07-13 19:22:41 -07:00
|
|
|
|
spaces
|
2012-01-29 23:54:00 -08:00
|
|
|
|
optional $ try $ controlSeq "setlength" *> grouped (controlSeq "itemindent") *> braced
|
2007-11-03 23:27:58 +00:00
|
|
|
|
spaces
|
2012-01-29 23:54:00 -08:00
|
|
|
|
start <- option 1 $ try $ do controlSeq "setcounter"
|
|
|
|
|
grouped (string "enum" *> many1 (oneOf "iv"))
|
|
|
|
|
optional sp
|
|
|
|
|
num <- grouped (many1 digit)
|
|
|
|
|
spaces
|
2015-04-12 09:47:13 +03:00
|
|
|
|
return (read num + 1 :: Int)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
bs <- listenv "enumerate" (many item)
|
|
|
|
|
return $ orderedListWith (start, style, delim) bs
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
paragraph :: PandocMonad m => LP m Blocks
|
2012-01-29 23:54:00 -08:00
|
|
|
|
paragraph = do
|
2013-02-20 13:01:36 -08:00
|
|
|
|
x <- trimInlines . mconcat <$> many1 inline
|
2012-01-29 23:54:00 -08:00
|
|
|
|
if x == mempty
|
|
|
|
|
then return mempty
|
2013-02-20 13:01:36 -08:00
|
|
|
|
else return $ para x
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
preamble :: PandocMonad m => LP m Blocks
|
2012-01-29 23:54:00 -08:00
|
|
|
|
preamble = mempty <$> manyTill preambleBlock beginDoc
|
2014-06-16 17:43:56 -07:00
|
|
|
|
where beginDoc = lookAhead $ try $ controlSeq "begin" *> string "{document}"
|
2015-04-12 09:47:13 +03:00
|
|
|
|
preambleBlock = void comment
|
|
|
|
|
<|> void sp
|
|
|
|
|
<|> void blanklines
|
2016-12-03 23:03:14 +01:00
|
|
|
|
<|> void include
|
2015-04-12 09:47:13 +03:00
|
|
|
|
<|> void macro
|
|
|
|
|
<|> void blockCommand
|
|
|
|
|
<|> void anyControlSeq
|
|
|
|
|
<|> void braced
|
|
|
|
|
<|> void anyChar
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
|
|
|
|
-------
|
|
|
|
|
|
|
|
|
|
-- citations
|
|
|
|
|
|
2012-02-10 21:47:36 -08:00
|
|
|
|
addPrefix :: [Inline] -> [Citation] -> [Citation]
|
2017-03-04 13:03:41 +01:00
|
|
|
|
addPrefix p (k:ks) = k {citationPrefix = p ++ citationPrefix k} : ks
|
|
|
|
|
addPrefix _ _ = []
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
2012-02-10 21:47:36 -08:00
|
|
|
|
addSuffix :: [Inline] -> [Citation] -> [Citation]
|
2012-01-29 23:54:00 -08:00
|
|
|
|
addSuffix s ks@(_:_) =
|
2013-07-21 11:44:49 -07:00
|
|
|
|
let k = last ks
|
|
|
|
|
in init ks ++ [k {citationSuffix = citationSuffix k ++ s}]
|
2012-01-29 23:54:00 -08:00
|
|
|
|
addSuffix _ _ = []
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
simpleCiteArgs :: PandocMonad m => LP m [Citation]
|
2012-01-29 23:54:00 -08:00
|
|
|
|
simpleCiteArgs = try $ do
|
2012-02-10 21:47:36 -08:00
|
|
|
|
first <- optionMaybe $ toList <$> opt
|
|
|
|
|
second <- optionMaybe $ toList <$> opt
|
2017-03-05 11:10:11 +01:00
|
|
|
|
keys <- try $ bgroup *> (manyTill citationLabel egroup)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
let (pre, suf) = case (first , second ) of
|
|
|
|
|
(Just s , Nothing) -> (mempty, s )
|
|
|
|
|
(Just s , Just t ) -> (s , t )
|
|
|
|
|
_ -> (mempty, mempty)
|
|
|
|
|
conv k = Citation { citationId = k
|
|
|
|
|
, citationPrefix = []
|
|
|
|
|
, citationSuffix = []
|
|
|
|
|
, citationMode = NormalCitation
|
|
|
|
|
, citationHash = 0
|
|
|
|
|
, citationNoteNum = 0
|
|
|
|
|
}
|
|
|
|
|
return $ addPrefix pre $ addSuffix suf $ map conv keys
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
citationLabel :: PandocMonad m => LP m String
|
2013-10-21 09:33:10 -07:00
|
|
|
|
citationLabel = optional sp *>
|
|
|
|
|
(many1 (satisfy isBibtexKeyChar)
|
|
|
|
|
<* optional sp
|
|
|
|
|
<* optional (char ',')
|
|
|
|
|
<* optional sp)
|
2016-07-29 20:53:43 +02:00
|
|
|
|
where isBibtexKeyChar c = isAlphaNum c || c `elem` (".:;?!`'()/*@_+=-[]" :: String)
|
2007-11-03 23:27:58 +00:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
cites :: PandocMonad m => CitationMode -> Bool -> LP m [Citation]
|
2012-01-29 23:54:00 -08:00
|
|
|
|
cites mode multi = try $ do
|
|
|
|
|
cits <- if multi
|
|
|
|
|
then many1 simpleCiteArgs
|
|
|
|
|
else count 1 simpleCiteArgs
|
2013-10-21 09:33:10 -07:00
|
|
|
|
let cs = concat cits
|
2012-01-29 23:54:00 -08:00
|
|
|
|
return $ case mode of
|
2013-10-21 09:33:10 -07:00
|
|
|
|
AuthorInText -> case cs of
|
|
|
|
|
(c:rest) -> c {citationMode = mode} : rest
|
|
|
|
|
[] -> []
|
|
|
|
|
_ -> map (\a -> a {citationMode = mode}) cs
|
2011-01-07 10:15:48 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
citation :: PandocMonad m => String -> CitationMode -> Bool -> LP m Inlines
|
2012-10-21 23:16:23 -07:00
|
|
|
|
citation name mode multi = do
|
|
|
|
|
(c,raw) <- withRaw $ cites mode multi
|
2013-03-17 08:48:29 -07:00
|
|
|
|
return $ cite c (rawInline "latex" $ "\\" ++ name ++ raw)
|
2012-01-29 23:54:00 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
complexNatbibCitation :: PandocMonad m => CitationMode -> LP m Inlines
|
2012-01-29 23:54:00 -08:00
|
|
|
|
complexNatbibCitation mode = try $ do
|
2012-02-10 21:47:36 -08:00
|
|
|
|
let ils = (toList . trimInlines . mconcat) <$>
|
2012-01-29 23:54:00 -08:00
|
|
|
|
many (notFollowedBy (oneOf "\\};") >> inline)
|
|
|
|
|
let parseOne = try $ do
|
|
|
|
|
skipSpaces
|
|
|
|
|
pref <- ils
|
|
|
|
|
cit' <- inline -- expect a citation
|
|
|
|
|
let citlist = toList cit'
|
|
|
|
|
cits' <- case citlist of
|
|
|
|
|
[Cite cs _] -> return cs
|
|
|
|
|
_ -> mzero
|
|
|
|
|
suff <- ils
|
|
|
|
|
skipSpaces
|
|
|
|
|
optional $ char ';'
|
2015-04-12 09:47:13 +03:00
|
|
|
|
return $ addPrefix pref $ addSuffix suff cits'
|
2012-02-06 12:41:34 -08:00
|
|
|
|
(c:cits, raw) <- withRaw $ grouped parseOne
|
2013-03-17 08:48:29 -07:00
|
|
|
|
return $ cite (c{ citationMode = mode }:cits)
|
|
|
|
|
(rawInline "latex" $ "\\citetext" ++ raw)
|
2011-01-07 10:15:48 -08:00
|
|
|
|
|
2012-01-29 23:54:00 -08:00
|
|
|
|
-- tables
|
2011-01-07 10:15:48 -08:00
|
|
|
|
|
2017-02-13 22:39:59 +01:00
|
|
|
|
parseAligns :: PandocMonad m => LP m [(String, Alignment, String)]
|
2011-01-07 10:15:48 -08:00
|
|
|
|
parseAligns = try $ do
|
2017-03-05 11:17:03 +01:00
|
|
|
|
bgroup
|
2015-03-08 15:47:39 +01:00
|
|
|
|
let maybeBar = skipMany $ sp <|> () <$ char '|' <|> () <$ (char '@' >> braced)
|
2013-08-28 16:54:37 -07:00
|
|
|
|
maybeBar
|
2012-03-19 08:18:32 -07:00
|
|
|
|
let cAlign = AlignCenter <$ char 'c'
|
|
|
|
|
let lAlign = AlignLeft <$ char 'l'
|
|
|
|
|
let rAlign = AlignRight <$ char 'r'
|
2014-04-06 15:11:18 -07:00
|
|
|
|
let parAlign = AlignLeft <$ (char 'p' >> braced)
|
2017-05-03 12:16:48 +02:00
|
|
|
|
-- algins from tabularx
|
|
|
|
|
let xAlign = AlignLeft <$ char 'X'
|
|
|
|
|
let mAlign = AlignLeft <$ (char 'm' >> braced)
|
|
|
|
|
let bAlign = AlignLeft <$ (char 'b' >> braced)
|
|
|
|
|
let alignChar = cAlign <|> lAlign <|> rAlign <|> parAlign <|> xAlign <|> mAlign <|> bAlign
|
2017-02-13 22:39:59 +01:00
|
|
|
|
let alignPrefix = char '>' >> braced
|
|
|
|
|
let alignSuffix = char '<' >> braced
|
|
|
|
|
let alignSpec = do
|
|
|
|
|
spaces
|
|
|
|
|
pref <- option "" alignPrefix
|
|
|
|
|
spaces
|
|
|
|
|
ch <- alignChar
|
|
|
|
|
spaces
|
|
|
|
|
suff <- option "" alignSuffix
|
|
|
|
|
return (pref, ch, suff)
|
|
|
|
|
aligns' <- sepEndBy alignSpec maybeBar
|
2012-01-29 23:54:00 -08:00
|
|
|
|
spaces
|
2017-03-05 11:17:03 +01:00
|
|
|
|
egroup
|
2011-01-07 10:15:48 -08:00
|
|
|
|
spaces
|
2017-02-13 22:39:59 +01:00
|
|
|
|
return $ aligns'
|
2011-01-07 10:15:48 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
hline :: PandocMonad m => LP m ()
|
2015-07-21 10:26:29 -07:00
|
|
|
|
hline = try $ do
|
|
|
|
|
spaces'
|
|
|
|
|
controlSeq "hline" <|>
|
|
|
|
|
-- booktabs rules:
|
|
|
|
|
controlSeq "toprule" <|>
|
|
|
|
|
controlSeq "bottomrule" <|>
|
2016-11-19 22:45:36 +01:00
|
|
|
|
controlSeq "midrule" <|>
|
|
|
|
|
controlSeq "endhead" <|>
|
|
|
|
|
controlSeq "endfirsthead"
|
2015-07-21 10:26:29 -07:00
|
|
|
|
spaces'
|
|
|
|
|
optional $ bracketed (many1 (satisfy (/=']')))
|
|
|
|
|
return ()
|
2011-01-07 10:15:48 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
lbreak :: PandocMonad m => LP m ()
|
2016-11-19 21:36:16 +01:00
|
|
|
|
lbreak = () <$ try (spaces' *>
|
|
|
|
|
(controlSeq "\\" <|> controlSeq "tabularnewline") <*
|
|
|
|
|
spaces')
|
2012-03-19 08:18:32 -07:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
amp :: PandocMonad m => LP m ()
|
2016-11-19 22:45:36 +01:00
|
|
|
|
amp = () <$ try (spaces' *> char '&' <* spaces')
|
2012-03-19 08:18:32 -07:00
|
|
|
|
|
2017-02-13 22:39:59 +01:00
|
|
|
|
parseTableRow :: PandocMonad m
|
|
|
|
|
=> Int -- ^ number of columns
|
|
|
|
|
-> [String] -- ^ prefixes
|
|
|
|
|
-> [String] -- ^ suffixes
|
2016-11-28 17:13:46 -05:00
|
|
|
|
-> LP m [Blocks]
|
2017-02-13 22:39:59 +01:00
|
|
|
|
parseTableRow cols prefixes suffixes = try $ do
|
|
|
|
|
let tableCellRaw = many (notFollowedBy
|
|
|
|
|
(amp <|> lbreak <|>
|
|
|
|
|
(() <$ try (string "\\end"))) >> anyChar)
|
2016-11-19 22:45:36 +01:00
|
|
|
|
let minipage = try $ controlSeq "begin" *> string "{minipage}" *>
|
|
|
|
|
env "minipage"
|
|
|
|
|
(skipopts *> spaces' *> optional braced *> spaces' *> blocks)
|
|
|
|
|
let tableCell = minipage <|>
|
2017-02-13 22:39:59 +01:00
|
|
|
|
((plain . trimInlines . mconcat) <$> many inline)
|
|
|
|
|
rawcells <- sepBy1 tableCellRaw amp
|
|
|
|
|
guard $ length rawcells == cols
|
|
|
|
|
let rawcells' = zipWith3 (\c p s -> p ++ trim c ++ s)
|
|
|
|
|
rawcells prefixes suffixes
|
|
|
|
|
cells' <- mapM (parseFromString tableCell) rawcells'
|
2014-06-17 00:38:55 -07:00
|
|
|
|
let numcells = length cells'
|
|
|
|
|
guard $ numcells <= cols && numcells >= 1
|
|
|
|
|
guard $ cells' /= [mempty]
|
|
|
|
|
-- note: a & b in a three-column table leaves an empty 3rd cell:
|
|
|
|
|
let cells'' = cells' ++ replicate (cols - numcells) mempty
|
2015-03-14 23:12:04 -07:00
|
|
|
|
spaces'
|
2014-06-17 00:38:55 -07:00
|
|
|
|
return cells''
|
2011-01-07 10:15:48 -08:00
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
spaces' :: PandocMonad m => LP m ()
|
2015-03-14 23:12:04 -07:00
|
|
|
|
spaces' = spaces *> skipMany (comment *> spaces)
|
|
|
|
|
|
2016-11-28 17:13:46 -05:00
|
|
|
|
simpTable :: PandocMonad m => Bool -> LP m Blocks
|
2015-01-01 08:46:45 -08:00
|
|
|
|
simpTable hasWidthParameter = try $ do
|
2015-03-14 23:12:04 -07:00
|
|
|
|
when hasWidthParameter $ () <$ (spaces' >> tok)
|
2015-03-08 15:30:05 +01:00
|
|
|
|
skipopts
|
2017-02-13 22:39:59 +01:00
|
|
|
|
(prefixes, aligns, suffixes) <- unzip3 <$> parseAligns
|
2012-01-29 23:54:00 -08:00
|
|
|
|
let cols = length aligns
|
2016-11-19 21:36:16 +01:00
|
|
|
|
optional $ controlSeq "caption" *> skipopts *> setCaption
|
|
|
|
|
optional lbreak
|
|
|
|
|
spaces'
|
|
|
|
|
skipMany hline
|
2016-11-19 22:45:36 +01:00
|
|
|
|
spaces'
|
2017-02-13 22:39:59 +01:00
|
|
|
|
header' <- option [] $ try (parseTableRow cols prefixes suffixes <*
|
|
|
|
|
lbreak <* many1 hline)
|
2016-11-19 22:45:36 +01:00
|
|
|
|
spaces'
|
2017-02-13 22:39:59 +01:00
|
|
|
|
rows <- sepEndBy (parseTableRow cols prefixes suffixes)
|
|
|
|
|
(lbreak <* optional (skipMany hline))
|
2016-11-19 21:36:16 +01:00
|
|
|
|
spaces'
|
|
|
|
|
optional $ controlSeq "caption" *> skipopts *> setCaption
|
|
|
|
|
optional lbreak
|
2015-03-14 23:12:04 -07:00
|
|
|
|
spaces'
|
2012-01-29 23:54:00 -08:00
|
|
|
|
let header'' = if null header'
|
|
|
|
|
then replicate cols mempty
|
|
|
|
|
else header'
|
2012-02-04 12:51:27 -08:00
|
|
|
|
lookAhead $ controlSeq "end" -- make sure we're at end
|
2012-01-29 23:54:00 -08:00
|
|
|
|
return $ table mempty (zip aligns (repeat 0)) header'' rows
|
2010-04-26 23:17:34 -07:00
|
|
|
|
|
2016-07-01 15:47:06 -07:00
|
|
|
|
removeDoubleQuotes :: String -> String
|
|
|
|
|
removeDoubleQuotes ('"':xs) =
|
|
|
|
|
case reverse xs of
|
|
|
|
|
'"':ys -> reverse ys
|
|
|
|
|
_ -> '"':xs
|
|
|
|
|
removeDoubleQuotes xs = xs
|