aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Citeproc/Locator.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Citeproc/Locator.hs')
-rw-r--r--src/Text/Pandoc/Citeproc/Locator.hs24
1 files changed, 20 insertions, 4 deletions
diff --git a/src/Text/Pandoc/Citeproc/Locator.hs b/src/Text/Pandoc/Citeproc/Locator.hs
index dba762c02..f8931d7b5 100644
--- a/src/Text/Pandoc/Citeproc/Locator.hs
+++ b/src/Text/Pandoc/Citeproc/Locator.hs
@@ -7,6 +7,7 @@ where
import Citeproc.Types
import Data.Text (Text)
import qualified Data.Text as T
+import Data.List (foldl')
import Text.Parsec
import Text.Pandoc.Definition
import Text.Pandoc.Parsing (romanNumeral)
@@ -19,7 +20,7 @@ parseLocator :: Locale -> [Inline] -> (Maybe (Text, Text), [Inline])
parseLocator locale inp =
case parse (pLocatorWords (toLocatorMap locale)) "suffix" $ splitInp inp of
Right r -> r
- Left _ -> (Nothing, inp)
+ Left _ -> (Nothing, maybeAddComma inp)
splitInp :: [Inline] -> [Inline]
splitInp = splitStrWhen (\c -> isSpace c || (isPunctuation c && c /= ':'))
@@ -41,9 +42,17 @@ pLocatorWords locMap = do
-- i.e. the first one will be " 9"
return $
if T.null la && T.null lo
- then (Nothing, s)
+ then (Nothing, maybeAddComma s)
else (Just (la, T.strip lo), s)
+maybeAddComma :: [Inline] -> [Inline]
+maybeAddComma [] = []
+maybeAddComma ils@(Space : _) = ils
+maybeAddComma ils@(Str t : _)
+ | Just (c, _) <- T.uncons t
+ , isPunctuation c = ils
+maybeAddComma ils = Str "," : Space : ils
+
pLocatorDelimited :: LocatorMap -> LocatorParser (Text, Text)
pLocatorDelimited locMap = try $ do
_ <- pMatchChar "{" (== '{')
@@ -96,7 +105,7 @@ pLocatorLabel' locMap lim = go ""
t <- anyToken
ts <- manyTill anyToken (try $ lookAhead lim)
let s = acc <> stringify (t:ts)
- case M.lookup (T.strip s) locMap of
+ case M.lookup (T.toCaseFold $ T.strip s) locMap of
-- try to find a longer one, or return this one
Just l -> go s <|> return (l, False)
Nothing -> go s
@@ -139,7 +148,7 @@ pBalancedBraces braces p = try $ do
where
except = notFollowedBy pBraces >> p
-- outer and inner
- surround = foldl (\a (open, close) -> sur open close except <|> a)
+ surround = foldl' (\a (open, close) -> sur open close except <|> a)
except
braces
@@ -180,6 +189,7 @@ pPageUnit = roman <|> plainUnit
plainUnit = do
ts <- many1 (notFollowedBy pSpace >>
notFollowedBy pLocatorPunct >>
+ notFollowedBy pMath >>
anyToken)
let s = stringify ts
-- otherwise look for actual digits or -s
@@ -210,6 +220,12 @@ pMatchChar msg f = satisfyTok f' <?> msg
pSpace :: LocatorParser Inline
pSpace = satisfyTok (\t -> isSpacey t || t == Str "\160") <?> "space"
+pMath :: LocatorParser Inline
+pMath = satisfyTok isMath
+ where
+ isMath (Math{}) = True
+ isMath _ = False
+
satisfyTok :: (Inline -> Bool) -> LocatorParser Inline
satisfyTok f = tokenPrim show (\sp _ _ -> sp) (\tok -> if f tok
then Just tok