aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Readers/LaTeX
diff options
context:
space:
mode:
authorJohn MacFarlane <[email protected]>2021-03-11 15:49:27 -0800
committerJohn MacFarlane <[email protected]>2021-03-13 15:05:37 -0800
commit8be95ad8e5150d5cab66c4abdf59baaf4670c6c8 (patch)
tree9655036efbaabda6a2a7802dc971c7fba5a987ca /src/Text/Pandoc/Readers/LaTeX
parent35b66a76718205c303f416bf0afc01c098e8a171 (diff)
Use custom Prelude based on relude.relude
The Prelude now longer exports partial functions, so a large number of uses of these functions in the code base have been rewritten. A .ghci file has been added; this is necessary for ghci to work properly with the custom Prelude. Currently there are lots of compiler warnings. We should either fix these or go to using a custom Prelude that changes less than relude.
Diffstat (limited to 'src/Text/Pandoc/Readers/LaTeX')
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Citation.hs27
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Inline.hs6
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/SIunitx.hs6
-rw-r--r--src/Text/Pandoc/Readers/LaTeX/Table.hs6
4 files changed, 23 insertions, 22 deletions
diff --git a/src/Text/Pandoc/Readers/LaTeX/Citation.hs b/src/Text/Pandoc/Readers/LaTeX/Citation.hs
index 655823dab..8e3b56220 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Citation.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Citation.hs
@@ -88,15 +88,15 @@ addPrefix p (k:ks) = k {citationPrefix = p ++ citationPrefix k} : ks
addPrefix _ _ = []
addSuffix :: [Inline] -> [Citation] -> [Citation]
-addSuffix s ks@(_:_) =
- let k = last ks
- in init ks ++ [k {citationSuffix = citationSuffix k ++ s}]
-addSuffix _ _ = []
+addSuffix s =
+ fromMaybe [] . viaNonEmpty
+ (\ks' -> let k = last ks'
+ in init ks' ++ [k {citationSuffix = citationSuffix k ++ s}])
simpleCiteArgs :: forall m . PandocMonad m => LP m Inlines -> LP m [Citation]
simpleCiteArgs inline = try $ do
- first <- optionMaybe $ toList <$> opt
- second <- optionMaybe $ toList <$> opt
+ first <- optionMaybe $ B.toList <$> opt
+ second <- optionMaybe $ B.toList <$> opt
keys <- try $ bgroup *> manyTill citationLabel egroup
let (pre, suf) = case (first , second ) of
(Just s , Nothing) -> (mempty, s )
@@ -140,8 +140,8 @@ cites inline mode multi = try $ do
let paropt = parenWrapped inline
cits <- if multi
then do
- multiprenote <- optionMaybe $ toList <$> paropt
- multipostnote <- optionMaybe $ toList <$> paropt
+ multiprenote <- optionMaybe $ B.toList <$> paropt
+ multipostnote <- optionMaybe $ B.toList <$> paropt
let (pre, suf) = case (multiprenote, multipostnote) of
(Just s , Nothing) -> (mempty, s)
(Nothing , Just t) -> (mempty, t)
@@ -149,10 +149,11 @@ cites inline mode multi = try $ do
_ -> (mempty, mempty)
tempCits <- many1 $ simpleCiteArgs inline
case tempCits of
- (k:ks) -> case ks of
- (_:_) -> return $ (addMprenote pre k : init ks) ++
- [addMpostnote suf (last ks)]
- _ -> return [addMprenote pre (addMpostnote suf k)]
+ (k:ks) ->
+ return $ fromMaybe [addMprenote pre (addMpostnote suf k)]
+ $ viaNonEmpty
+ (\ks' -> addMprenote pre k : init ks' ++
+ [addMpostnote suf (last ks')]) ks
_ -> return [[]]
else count 1 $ simpleCiteArgs inline
let cs = concat cits
@@ -183,7 +184,7 @@ handleCitationPart :: Inlines -> [Citation]
handleCitationPart ils =
let isCite Cite{} = True
isCite _ = False
- (pref, rest) = break isCite (toList ils)
+ (pref, rest) = break isCite (B.toList ils)
in case rest of
(Cite cs _:suff) -> addPrefix pref $ addSuffix suff cs
_ -> []
diff --git a/src/Text/Pandoc/Readers/LaTeX/Inline.hs b/src/Text/Pandoc/Readers/LaTeX/Inline.hs
index 7b8bca4af..6d14bf747 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Inline.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Inline.hs
@@ -25,7 +25,7 @@ where
import qualified Data.Map as M
import Data.Text (Text)
import qualified Data.Text as T
-import Text.Pandoc.Builder
+import Text.Pandoc.Builder as B
import Text.Pandoc.Shared (toRomanNumeral, safeRead)
import Text.Pandoc.Readers.LaTeX.Types (Tok (..), TokType (..))
import Control.Applicative (optional, (<|>))
@@ -162,8 +162,8 @@ 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 $
+ case B.toList ils of
+ (Str (T.uncons -> Just (x, xs)) : ys) -> return $ B.fromList $
-- try to normalize to the combined character:
Str (Normalize.normalize Normalize.NFC
(T.pack [x, combiningAccent]) <> xs) : ys
diff --git a/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs b/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs
index 1952f4e1a..991ec4d98 100644
--- a/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/SIunitx.hs
@@ -60,9 +60,9 @@ doSInumlist = do
case xs of
[] -> return mempty
[x] -> return x
- _ -> return $
- mconcat (intersperse (str "," <> space) (init xs)) <>
- text ", & " <> last xs
+ _ -> return $ fromMaybe mempty $ viaNonEmpty
+ (\xsNE -> mconcat (intersperse (str "," <> space) (init xsNE)) <>
+ text ", & " <> last xsNE) xs
parseNum :: Parser Text () Inlines
parseNum = (mconcat <$> many parseNumPart) <* eof
diff --git a/src/Text/Pandoc/Readers/LaTeX/Table.hs b/src/Text/Pandoc/Readers/LaTeX/Table.hs
index 7833da081..10d41912e 100644
--- a/src/Text/Pandoc/Readers/LaTeX/Table.hs
+++ b/src/Text/Pandoc/Readers/LaTeX/Table.hs
@@ -194,8 +194,8 @@ cellAlignment = skipMany (symbol '|') *> alignment <* skipMany (symbol '|')
_ -> AlignDefault
plainify :: Blocks -> Blocks
-plainify bs = case toList bs of
- [Para ils] -> plain (fromList ils)
+plainify bs = case B.toList bs of
+ [Para ils] -> plain (B.fromList ils)
_ -> bs
multirowCell :: PandocMonad m => LP m Blocks -> LP m Cell
@@ -231,7 +231,7 @@ multicolumnCell blocks = controlSeq "multicolumn" >> do
alignment
(RowSpan rs)
(ColSpan span')
- (fromList bs)
+ (B.fromList bs)
symbol '{' *> (nestedCell <|> singleCell) <* symbol '}'