diff options
| author | John MacFarlane <jgm@berkeley.edu> | 2021-03-03 18:21:32 -0800 | 
|---|---|---|
| committer | John MacFarlane <jgm@berkeley.edu> | 2021-03-03 18:21:32 -0800 | 
| commit | 33e4c8dd6c2bbc8109880f43b379d074ceb38391 (patch) | |
| tree | d28f22929f7f80a8f41f46c8490abf1f08efad3b /src/Text/Pandoc/Readers/LaTeX | |
| parent | da5e9e5956aae3ac83edef7831939553360b8964 (diff) | |
| download | pandoc-33e4c8dd6c2bbc8109880f43b379d074ceb38391.tar.gz | |
Remove T.P.Readers.LaTeX.Accent.
Incorporate accentCommands into T.P.Readers.LaTeX.Inline.
Diffstat (limited to 'src/Text/Pandoc/Readers/LaTeX')
| -rw-r--r-- | src/Text/Pandoc/Readers/LaTeX/Accent.hs | 78 | ||||
| -rw-r--r-- | src/Text/Pandoc/Readers/LaTeX/Inline.hs | 71 | 
2 files changed, 68 insertions, 81 deletions
| diff --git a/src/Text/Pandoc/Readers/LaTeX/Accent.hs b/src/Text/Pandoc/Readers/LaTeX/Accent.hs deleted file mode 100644 index f8c53491c..000000000 --- a/src/Text/Pandoc/Readers/LaTeX/Accent.hs +++ /dev/null @@ -1,78 +0,0 @@ -{-# LANGUAGE ViewPatterns #-} -{-# LANGUAGE OverloadedStrings #-} -module Text.Pandoc.Readers.LaTeX.Accent -  ( accentCommands ) -where - -import Text.Pandoc.Class -import Text.Pandoc.Readers.LaTeX.Parsing -import Text.Pandoc.Builder as B -import qualified Data.Map as M -import Data.Text (Text) -import Data.Maybe (fromMaybe) -import Text.Pandoc.Parsing -import qualified Data.Text as T -import qualified Data.Text.Normalize as Normalize - -accentCommands :: PandocMonad m => LP m Inlines -> M.Map Text (LP m Inlines) -accentCommands tok = -  let accent = accentWith tok -      lit = pure . str -  in M.fromList -  [ ("aa", lit "å") -  , ("AA", lit "Å") -  , ("ss", lit "ß") -  , ("o", lit "ø") -  , ("O", lit "Ø") -  , ("L", lit "Ł") -  , ("l", lit "ł") -  , ("ae", lit "æ") -  , ("AE", lit "Æ") -  , ("oe", lit "œ") -  , ("OE", lit "Œ") -  , ("pounds", lit "£") -  , ("euro", lit "€") -  , ("copyright", lit "©") -  , ("textasciicircum", lit "^") -  , ("textasciitilde", lit "~") -  , ("H", accent '\779' Nothing) -- hungarumlaut -  , ("`", accent '\768' (Just '`')) -- grave -  , ("'", accent '\769' (Just '\'')) -- acute -  , ("^", accent '\770' (Just '^')) -- circ -  , ("~", accent '\771' (Just '~')) -- tilde -  , ("\"", accent '\776' Nothing) -- umlaut -  , (".", accent '\775' Nothing) -- dot -  , ("=", accent '\772' Nothing) -- macron -  , ("|", accent '\781' Nothing) -- vertical line above -  , ("b", accent '\817' Nothing) -- macron below -  , ("c", accent '\807' Nothing) -- cedilla -  , ("G", accent '\783' Nothing) -- doublegrave -  , ("h", accent '\777' Nothing) -- hookabove -  , ("d", accent '\803' Nothing) -- dotbelow -  , ("f", accent '\785' Nothing)  -- inverted breve -  , ("r", accent '\778' Nothing)  -- ringabove -  , ("t", accent '\865' Nothing)  -- double inverted breve -  , ("U", accent '\782' Nothing)  -- double vertical line above -  , ("v", accent '\780' Nothing) -- hacek -  , ("u", accent '\774' Nothing) -- breve -  , ("k", accent '\808' Nothing) -- ogonek -  , ("textogonekcentered", accent '\808' Nothing) -- ogonek -  , ("i", lit "ı")  -- dotless i -  , ("j", lit "ȷ")  -- dotless j -  , ("newtie", accent '\785' Nothing) -- inverted breve -  , ("textcircled", accent '\8413' Nothing) -- combining circle -  ] - -accentWith :: PandocMonad m -           => LP m Inlines -> Char -> Maybe Char -> LP m Inlines -accentWith tok combiningAccent fallBack = try $ do -  ils <- tok -  case toList ils of -       (Str (T.uncons -> Just (x, xs)) : ys) -> return $ fromList $ -         -- try to normalize to the combined character: -         Str (Normalize.normalize Normalize.NFC -               (T.pack [x, combiningAccent]) <> xs) : ys -       [Space]           -> return $ str $ T.singleton $ fromMaybe combiningAccent fallBack -       []                -> return $ str $ T.singleton $ fromMaybe combiningAccent fallBack -       _                 -> return ils - diff --git a/src/Text/Pandoc/Readers/LaTeX/Inline.hs b/src/Text/Pandoc/Readers/LaTeX/Inline.hs index 8bdff58f7..7b8bca4af 100644 --- a/src/Text/Pandoc/Readers/LaTeX/Inline.hs +++ b/src/Text/Pandoc/Readers/LaTeX/Inline.hs @@ -1,4 +1,5 @@  {-# LANGUAGE OverloadedStrings     #-} +{-# LANGUAGE ViewPatterns          #-}  {- |     Module      : Text.Pandoc.Readers.LaTeX.Inline     Copyright   : Copyright (C) 2006-2021 John MacFarlane @@ -12,6 +13,7 @@ module Text.Pandoc.Readers.LaTeX.Inline    ( acronymCommands    , verbCommands    , charCommands +  , accentCommands    , nameCommands    , biblatexInlineCommands    , refCommands @@ -33,11 +35,12 @@ import Text.Pandoc.Readers.LaTeX.Parsing  import Text.Pandoc.Extensions (extensionEnabled, Extension(..))  import Text.Pandoc.Parsing (getOption, updateState, getState, notFollowedBy,                              manyTill, getInput, setInput, incSourceColumn, -                            option, many1) +                            option, many1, try)  import Data.Char (isDigit)  import Text.Pandoc.Highlighting (fromListingsLanguage,) -import Data.Maybe (maybeToList) +import Data.Maybe (maybeToList, fromMaybe)  import Text.Pandoc.Options (ReaderOptions(..)) +import qualified Data.Text.Normalize as Normalize  import qualified Text.Pandoc.Translations as Translations  rawInlineOr :: PandocMonad m => Text -> LP m Inlines -> LP m Inlines @@ -155,6 +158,22 @@ romanNumeralArg = spaces *> (parser <|> inBraces)          Prelude.fail "Non-digits in argument to \\Rn or \\RN"        safeRead digits +accentWith :: PandocMonad m +           => LP m Inlines -> Char -> Maybe Char -> LP m Inlines +accentWith tok combiningAccent fallBack = try $ do +  ils <- tok +  case toList ils of +       (Str (T.uncons -> Just (x, xs)) : ys) -> return $ fromList $ +         -- try to normalize to the combined character: +         Str (Normalize.normalize Normalize.NFC +               (T.pack [x, combiningAccent]) <> xs) : ys +       [Space] -> return $ str $ T.singleton +                         $ fromMaybe combiningAccent fallBack +       []      -> return $ str $ T.singleton +                         $ fromMaybe combiningAccent fallBack +       _       -> return ils + +  verbCommands :: PandocMonad m => M.Map Text (LP m Inlines)  verbCommands = M.fromList    [ ("verb", doverb) @@ -163,7 +182,53 @@ verbCommands = M.fromList    , ("Verb", doverb)    ] - +accentCommands :: PandocMonad m => LP m Inlines -> M.Map Text (LP m Inlines) +accentCommands tok = +  let accent = accentWith tok +  in  M.fromList +  [ ("aa", lit "å") +  , ("AA", lit "Å") +  , ("ss", lit "ß") +  , ("o", lit "ø") +  , ("O", lit "Ø") +  , ("L", lit "Ł") +  , ("l", lit "ł") +  , ("ae", lit "æ") +  , ("AE", lit "Æ") +  , ("oe", lit "œ") +  , ("OE", lit "Œ") +  , ("pounds", lit "£") +  , ("euro", lit "€") +  , ("copyright", lit "©") +  , ("textasciicircum", lit "^") +  , ("textasciitilde", lit "~") +  , ("H", accent '\779' Nothing) -- hungarumlaut +  , ("`", accent '\768' (Just '`')) -- grave +  , ("'", accent '\769' (Just '\'')) -- acute +  , ("^", accent '\770' (Just '^')) -- circ +  , ("~", accent '\771' (Just '~')) -- tilde +  , ("\"", accent '\776' Nothing) -- umlaut +  , (".", accent '\775' Nothing) -- dot +  , ("=", accent '\772' Nothing) -- macron +  , ("|", accent '\781' Nothing) -- vertical line above +  , ("b", accent '\817' Nothing) -- macron below +  , ("c", accent '\807' Nothing) -- cedilla +  , ("G", accent '\783' Nothing) -- doublegrave +  , ("h", accent '\777' Nothing) -- hookabove +  , ("d", accent '\803' Nothing) -- dotbelow +  , ("f", accent '\785' Nothing)  -- inverted breve +  , ("r", accent '\778' Nothing)  -- ringabove +  , ("t", accent '\865' Nothing)  -- double inverted breve +  , ("U", accent '\782' Nothing)  -- double vertical line above +  , ("v", accent '\780' Nothing) -- hacek +  , ("u", accent '\774' Nothing) -- breve +  , ("k", accent '\808' Nothing) -- ogonek +  , ("textogonekcentered", accent '\808' Nothing) -- ogonek +  , ("i", lit "ı")  -- dotless i +  , ("j", lit "ȷ")  -- dotless j +  , ("newtie", accent '\785' Nothing) -- inverted breve +  , ("textcircled", accent '\8413' Nothing) -- combining circle +  ]  charCommands :: PandocMonad m => M.Map Text (LP m Inlines)  charCommands = M.fromList | 
