From 5817e864918e5d03b6402afac0ff8c748a2ac2f6 Mon Sep 17 00:00:00 2001
From: John MacFarlane <jgm@berkeley.edu>
Date: Tue, 14 Dec 2021 09:20:09 -0800
Subject: Org reader: remove support for "Berkeley style" citations.

See #7329.
---
 src/Text/Pandoc/Readers/Org/Inlines.hs    | 187 +++++++-----------------------
 test/Tests/Readers/Org/Inline/Citation.hs |  47 --------
 2 files changed, 42 insertions(+), 192 deletions(-)

diff --git a/src/Text/Pandoc/Readers/Org/Inlines.hs b/src/Text/Pandoc/Readers/Org/Inlines.hs
index 6862dd71e..2366aa290 100644
--- a/src/Text/Pandoc/Readers/Org/Inlines.hs
+++ b/src/Text/Pandoc/Readers/Org/Inlines.hs
@@ -32,10 +32,9 @@ import Text.TeXMath (DisplayType (..), readTeX, writePandoc)
 import Text.Pandoc.Sources (ToSources(..))
 import qualified Text.TeXMath.Readers.MathML.EntityMap as MathMLEntityMap
 
-import Control.Monad (guard, mplus, mzero, unless, void, when)
+import Control.Monad (guard, mplus, mzero, unless, when)
 import Control.Monad.Trans (lift)
 import Data.Char (isAlphaNum, isSpace)
-import Data.List (intersperse)
 import qualified Data.Map as M
 import Data.Text (Text)
 import qualified Data.Text as T
@@ -148,32 +147,57 @@ endline = try $ do
 -- Citations
 --
 
--- The state of citations is a bit confusing due to the lack of an official
--- syntax and multiple syntaxes coexisting.  The pandocOrgCite syntax was the
--- first to be implemented here and is almost identical to Markdown's citation
--- syntax.  The org-ref package is in wide use to handle citations, but the
--- syntax is a bit limiting and not quite as simple to write.  The
--- semi-official Org-mode citation syntax is based on John MacFarlane's Pandoc
--- sytax and Org-oriented enhancements contributed by Richard Lawrence and
--- others.  It's dubbed Berkeley syntax due the place of activity of its main
--- contributors.  All this should be consolidated once an official Org-mode
--- citation syntax has emerged.
+-- We first try to parse official org-cite citations, then fall
+-- back to org-ref citations (which are still in wide use).
 
 cite :: PandocMonad m => OrgParser m (F Inlines)
-cite = try $ berkeleyCite <|> do
+cite = try $ do
   guardEnabled Ext_citations
   (cs, raw) <- withRaw $ choice
-               [ pandocOrgCite
+               [ orgCite
                , orgRefCite
-               , berkeleyTextualCite
                ]
   return $ flip B.cite (B.text raw) <$> cs
 
--- | A citation in Pandoc Org-mode style (@[prefix \@citekey suffix]@).
-pandocOrgCite :: PandocMonad m => OrgParser m (F [Citation])
-pandocOrgCite = try $
+-- | A citation in org-cite style
+orgCite :: PandocMonad m => OrgParser m (F [Citation])
+orgCite = try $
   char '[' *> skipSpaces *> citeList <* skipSpaces <* char ']'
 
+citeList :: PandocMonad m => OrgParser m (F [Citation])
+citeList = sequence <$> sepEndBy1 citation (try $ char ';' *> skipSpaces)
+
+citation :: PandocMonad m => OrgParser m (F Citation)
+citation = try $ do
+  pref <- prefix
+  (suppress_author, key) <- citeKey False
+  suff <- suffix
+  return $ do
+    x <- pref
+    y <- suff
+    return Citation
+      { citationId      = key
+      , citationPrefix  = B.toList x
+      , citationSuffix  = B.toList y
+      , citationMode    = if suppress_author
+                          then SuppressAuthor
+                          else NormalCitation
+      , citationNoteNum = 0
+      , citationHash    = 0
+      }
+ where
+   prefix = trimInlinesF . mconcat <$>
+            manyTill inline (char ']' <|> (']' <$ lookAhead (citeKey False)))
+   suffix = try $ do
+     hasSpace <- option False (notFollowedBy nonspaceChar >> return True)
+     skipSpaces
+     rest <- trimInlinesF . mconcat <$>
+             many (notFollowedBy (oneOf ";]") *> inline)
+     return $ if hasSpace
+              then (B.space <>) <$> rest
+              else rest
+
+
 orgRefCite :: PandocMonad m => OrgParser m (F [Citation])
 orgRefCite = try $ choice
   [ normalOrgRefCite
@@ -201,100 +225,6 @@ normalOrgRefCite = try $ do
      , citationHash    = 0
      }
 
--- | Read an Berkeley-style Org-mode citation.  Berkeley citation style was
--- develop and adjusted to Org-mode style by John MacFarlane and Richard
--- Lawrence, respectively, both philosophers at UC Berkeley.
-berkeleyCite :: PandocMonad m => OrgParser m (F Inlines)
-berkeleyCite = try $ do
-  bcl <- berkeleyCitationList
-  return $ do
-    parens <- berkeleyCiteParens <$> bcl
-    prefix <- berkeleyCiteCommonPrefix <$> bcl
-    suffix <- berkeleyCiteCommonSuffix <$> bcl
-    citationList <- berkeleyCiteCitations <$> bcl
-    return $
-      if parens
-      then toCite
-           . maybe id (alterFirst . prependPrefix) prefix
-           . maybe id (alterLast . appendSuffix) suffix
-           $ citationList
-      else maybe mempty (<> " ") prefix
-             <> toListOfCites (map toInTextMode citationList)
-             <> maybe mempty (", " <>) suffix
- where
-   toCite :: [Citation] -> Inlines
-   toCite cs = B.cite cs mempty
-
-   toListOfCites :: [Citation] -> Inlines
-   toListOfCites = mconcat . intersperse ", " . map (\c -> B.cite [c] mempty)
-
-   toInTextMode :: Citation -> Citation
-   toInTextMode c = c { citationMode = AuthorInText }
-
-   alterFirst, alterLast :: (a -> a) -> [a] -> [a]
-   alterFirst _ []     = []
-   alterFirst f (c:cs) = f c : cs
-   alterLast  f = reverse . alterFirst f . reverse
-
-   prependPrefix, appendSuffix :: Inlines -> Citation -> Citation
-   prependPrefix pre c = c { citationPrefix = B.toList pre <> citationPrefix c }
-   appendSuffix  suf c = c { citationSuffix = citationSuffix c <> B.toList suf }
-
-data BerkeleyCitationList = BerkeleyCitationList
-  { berkeleyCiteParens       :: Bool
-  , berkeleyCiteCommonPrefix :: Maybe Inlines
-  , berkeleyCiteCommonSuffix :: Maybe Inlines
-  , berkeleyCiteCitations    :: [Citation]
-  }
-berkeleyCitationList :: PandocMonad m => OrgParser m (F BerkeleyCitationList)
-berkeleyCitationList = try $ do
-  char '['
-  parens <- choice [ False <$ berkeleyBareTag, True <$ berkeleyParensTag ]
-  char ':'
-  skipSpaces
-  commonPrefix <- optionMaybe (try $ citationListPart <* char ';')
-  citations    <- citeList
-  commonSuffix <- optionMaybe (try citationListPart)
-  char ']'
-  return (BerkeleyCitationList parens
-    <$> sequence commonPrefix
-    <*> sequence commonSuffix
-    <*> citations)
- where
-   citationListPart :: PandocMonad m => OrgParser m (F Inlines)
-   citationListPart = fmap (trimInlinesF . mconcat) . try . many1 $ do
-     notFollowedBy' $ citeKey False
-     notFollowedBy (oneOf ";]")
-     inline
-
-berkeleyBareTag :: PandocMonad m => OrgParser m ()
-berkeleyBareTag = try $ void berkeleyBareTag'
-
-berkeleyParensTag :: PandocMonad m => OrgParser m ()
-berkeleyParensTag = try . void $ enclosedByPair1 '(' ')' berkeleyBareTag'
-
-berkeleyBareTag' :: PandocMonad m => OrgParser m ()
-berkeleyBareTag' = try $ void (string "cite")
-
-berkeleyTextualCite :: PandocMonad m => OrgParser m (F [Citation])
-berkeleyTextualCite = try $ do
-  (suppressAuthor, key) <- citeKey False
-  returnF . return $ Citation
-    { citationId      = key
-    , citationPrefix  = mempty
-    , citationSuffix  = mempty
-    , citationMode    = if suppressAuthor then SuppressAuthor else AuthorInText
-    , citationNoteNum = 0
-    , citationHash    = 0
-    }
-
--- The following is what a Berkeley-style bracketed textual citation parser
--- would look like.  However, as these citations are a subset of Pandoc's Org
--- citation style, this isn't used.
--- berkeleyBracketedTextualCite :: PandocMonad m => OrgParser m (F [Citation])
--- berkeleyBracketedTextualCite = try . (fmap head) $
---   enclosedByPair1 '[' ']' berkeleyTextualCite
-
 -- | Read a link-like org-ref style citation.  The citation includes pre and
 -- post text.  However, multiple citations are not possible due to limitations
 -- in the syntax.
@@ -345,39 +275,6 @@ orgRefCiteMode =
     , ("citeyear", SuppressAuthor)
     ]
 
-citeList :: PandocMonad m => OrgParser m (F [Citation])
-citeList = sequence <$> sepEndBy1 citation (try $ char ';' *> skipSpaces)
-
-citation :: PandocMonad m => OrgParser m (F Citation)
-citation = try $ do
-  pref <- prefix
-  (suppress_author, key) <- citeKey False
-  suff <- suffix
-  return $ do
-    x <- pref
-    y <- suff
-    return Citation
-      { citationId      = key
-      , citationPrefix  = B.toList x
-      , citationSuffix  = B.toList y
-      , citationMode    = if suppress_author
-                          then SuppressAuthor
-                          else NormalCitation
-      , citationNoteNum = 0
-      , citationHash    = 0
-      }
- where
-   prefix = trimInlinesF . mconcat <$>
-            manyTill inline (char ']' <|> (']' <$ lookAhead (citeKey False)))
-   suffix = try $ do
-     hasSpace <- option False (notFollowedBy nonspaceChar >> return True)
-     skipSpaces
-     rest <- trimInlinesF . mconcat <$>
-             many (notFollowedBy (oneOf ";]") *> inline)
-     return $ if hasSpace
-              then (B.space <>) <$> rest
-              else rest
-
 footnote :: PandocMonad m => OrgParser m (F Inlines)
 footnote = try $ do
   note <- inlineNote <|> referencedNote
diff --git a/test/Tests/Readers/Org/Inline/Citation.hs b/test/Tests/Readers/Org/Inline/Citation.hs
index a11804983..7eabd9aae 100644
--- a/test/Tests/Readers/Org/Inline/Citation.hs
+++ b/test/Tests/Readers/Org/Inline/Citation.hs
@@ -169,53 +169,6 @@ tests =
       in (para $ cite [citation] "[[citep:Dominik201408][See page 20::, for example]]")
     ]
 
-  , testGroup "Berkeley-style citations" $
-    let pandocCite = Citation
-          { citationId = "Pandoc"
-          , citationPrefix = mempty
-          , citationSuffix = mempty
-          , citationMode = NormalCitation
-          , citationNoteNum = 0
-          , citationHash = 0
-          }
-        pandocInText = pandocCite { citationMode = AuthorInText }
-        dominikCite = Citation
-          { citationId = "Dominik201408"
-          , citationPrefix = mempty
-          , citationSuffix = mempty
-          , citationMode = NormalCitation
-          , citationNoteNum = 0
-          , citationHash = 0
-          }
-        dominikInText = dominikCite { citationMode = AuthorInText }
-    in
-      [ "Berkeley-style in-text citation" =:
-        "See @Dominik201408." =?>
-        para ("See "
-               <> cite [dominikInText] "@Dominik201408"
-               <> ".")
-
-      , "Berkeley-style parenthetical citation list" =:
-        "[(cite): see; @Dominik201408;also @Pandoc; and others]" =?>
-        let pandocCite'  = pandocCite {
-                             citationPrefix = toList "also"
-                           , citationSuffix = toList "and others"
-                           }
-            dominikCite' = dominikCite {
-                             citationPrefix = toList "see"
-                           }
-        in (para $ cite [dominikCite', pandocCite'] "")
-
-      , "Berkeley-style plain citation list" =:
-        "[cite: See; @Dominik201408; and @Pandoc; and others]" =?>
-        let pandocCite' = pandocInText { citationPrefix = toList "and" }
-        in (para $ "See "
-             <> cite [dominikInText] ""
-             <> "," <> space
-             <> cite [pandocCite'] ""
-             <> "," <> space <> "and others")
-    ]
-
   , "LaTeX citation" =:
     "\\cite{Coffee}" =?>
     let citation = Citation
-- 
cgit v1.2.3