diff options
Diffstat (limited to 'src/Text/Pandoc/Readers/LaTeX.hs')
-rw-r--r-- | src/Text/Pandoc/Readers/LaTeX.hs | 104 |
1 files changed, 83 insertions, 21 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index 3292550b2..d0e95bd85 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -44,7 +44,7 @@ import Control.Applicative (many, optional, (<|>)) import Control.Monad import Control.Monad.Except (throwError) import Control.Monad.Trans (lift) -import Data.Char (chr, isAlphaNum, isLetter, ord, isDigit) +import Data.Char (chr, isAlphaNum, isLetter, ord, isDigit, toLower) import Data.Default import Data.Text (Text) import qualified Data.Text as T @@ -770,11 +770,13 @@ keyval = try $ do keyvals :: PandocMonad m => LP m [(String, String)] keyvals = try $ symbol '[' >> manyTill keyval (symbol ']') -accent :: (Char -> String) -> Inlines -> LP m Inlines -accent f ils = +accent :: PandocMonad m => Char -> (Char -> String) -> LP m Inlines +accent c f = try $ do + ils <- tok case toList ils of (Str (x:xs) : ys) -> return $ fromList (Str (f x ++ xs) : ys) - [] -> mzero + [Space] -> return $ str [c] + [] -> return $ str [c] _ -> return ils grave :: Char -> String @@ -961,6 +963,19 @@ hacek 'Z' = "Ž" hacek 'z' = "ž" hacek c = [c] +ogonek :: Char -> String +ogonek 'a' = "ą" +ogonek 'e' = "ę" +ogonek 'o' = "ǫ" +ogonek 'i' = "į" +ogonek 'u' = "ų" +ogonek 'A' = "Ą" +ogonek 'E' = "Ę" +ogonek 'I' = "Į" +ogonek 'O' = "Ǫ" +ogonek 'U' = "Ų" +ogonek c = [c] + breve :: Char -> String breve 'A' = "Ă" breve 'a' = "ă" @@ -1275,17 +1290,19 @@ inlineCommands = M.fromList $ , ("copyright", lit "©") , ("textasciicircum", lit "^") , ("textasciitilde", lit "~") - , ("H", try $ tok >>= accent hungarumlaut) - , ("`", 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) - , ("v", option (str "v") $ try $ tok >>= accent hacek) - , ("u", option (str "u") $ try $ tok >>= accent breve) + , ("H", accent '\779' hungarumlaut) + , ("`", accent '`' grave) + , ("'", accent '\'' acute) + , ("^", accent '^' circ) + , ("~", accent '~' tilde) + , ("\"", accent '\776' umlaut) + , (".", accent '\775' dot) + , ("=", accent '\772' macron) + , ("c", accent '\807' cedilla) + , ("v", accent 'ˇ' hacek) + , ("u", accent '\774' breve) + , ("k", accent '\808' ogonek) + , ("textogonekcentered", accent '\808' ogonek) , ("i", lit "i") , ("\\", linebreak <$ (do inTableCell <- sInTableCell <$> getState guard $ not inTableCell @@ -1391,11 +1408,8 @@ inlineCommands = M.fromList $ <|> citation "citeauthor" AuthorInText False) , ("nocite", mempty <$ (citation "nocite" NormalCitation False >>= addMeta "nocite")) - -- hyperlink: for now, we just preserve contents. - -- we might add the actual links, but we need to avoid clashes - -- with ids produced by label. - , ("hypertarget", braced >> tok) - , ("hyperlink", braced >> tok) + , ("hyperlink", hyperlink) + , ("hypertarget", hypertargetInline) -- glossaries package , ("gls", doAcronym "short") , ("Gls", doAcronym "short") @@ -1445,8 +1459,56 @@ inlineCommands = M.fromList $ , ("toggletrue", braced >>= setToggle True) , ("togglefalse", braced >>= setToggle False) , ("iftoggle", try $ ifToggle >> inline) + -- biblatex misc + , ("RN", romanNumeralUpper) + , ("Rn", romanNumeralLower) ] +hyperlink :: PandocMonad m => LP m Inlines +hyperlink = try $ do + src <- toksToString <$> braced + lab <- tok + return $ link ('#':src) "" lab + +hypertargetBlock :: PandocMonad m => LP m Blocks +hypertargetBlock = try $ do + ref <- toksToString <$> braced + bs <- grouped block + case toList bs of + [Header 1 (ident,_,_) _] | ident == ref -> return bs + _ -> return $ divWith (ref, [], []) bs + +hypertargetInline :: PandocMonad m => LP m Inlines +hypertargetInline = try $ do + ref <- toksToString <$> braced + ils <- grouped inline + return $ spanWith (ref, [], []) ils + +romanNumeralUpper :: (PandocMonad m) => LP m Inlines +romanNumeralUpper = + str . toRomanNumeral <$> romanNumeralArg + +romanNumeralLower :: (PandocMonad m) => LP m Inlines +romanNumeralLower = + str . map toLower . toRomanNumeral <$> romanNumeralArg + +romanNumeralArg :: (PandocMonad m) => LP m Int +romanNumeralArg = spaces *> (parser <|> inBraces) + where + inBraces = do + symbol '{' + spaces + res <- parser + spaces + symbol '}' + return res + parser = do + Tok _ Word s <- satisfyTok isWordTok + let (digits, rest) = T.span isDigit s + unless (T.null rest) $ + fail "Non-digits in argument to \\Rn or \\RN" + safeRead $ T.unpack digits + newToggle :: (Monoid a, PandocMonad m) => [Tok] -> LP m a newToggle name = do updateState $ \st -> @@ -1944,7 +2006,7 @@ blockCommands = M.fromList $ , ("setdefaultlanguage", setDefaultLanguage) , ("setmainlanguage", setDefaultLanguage) -- hyperlink - , ("hypertarget", try $ braced >> grouped block) + , ("hypertarget", hypertargetBlock) -- LaTeX colors , ("textcolor", coloredBlock "color") , ("colorbox", coloredBlock "background-color") |