{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Readers.RIS
  ( readRIS
  )
where
import Text.Pandoc.Options
import Text.Pandoc.Definition
import Text.Pandoc.Parsing
import Data.Char (isAsciiUpper, isDigit, isSpace, ord, chr)
import Data.List (foldl')
import Citeproc (Reference(..), ItemId(..), Val(..), Date(..), DateParts(..),
                 toVariable)
import Text.Pandoc.Builder as B
import Text.Pandoc.Class (PandocMonad)
import Text.Pandoc.Citeproc.MetaValue (referenceToMetaValue)
import Text.Pandoc.Citeproc.Name (toName, NameOpts(..))
import Control.Monad.Except (throwError)
import qualified Data.Text as T
import Data.Text (Text)
import Data.Maybe (fromMaybe)
import qualified Data.Map as M
import Safe (readMay)
readRIS :: (PandocMonad m, ToSources a)
        => ReaderOptions -> a -> m Pandoc
readRIS :: forall (m :: * -> *) a.
(PandocMonad m, ToSources a) =>
ReaderOptions -> a -> m Pandoc
readRIS ReaderOptions
_opts a
inp = do
  Either PandocError [Reference Text]
parsed <- ParsecT Sources () m [Reference Text]
-> () -> a -> m (Either PandocError [Reference Text])
forall (m :: * -> *) t st a.
(Monad m, ToSources t) =>
ParsecT Sources st m a -> st -> t -> m (Either PandocError a)
readWithM ParsecT Sources () m [Reference Text]
forall (m :: * -> *). PandocMonad m => RISParser m [Reference Text]
risReferences () a
inp
  case Either PandocError [Reference Text]
parsed of
    Right [Reference Text]
refs -> do
      [Reference Inlines]
refs' <- (Reference Text -> m (Reference Inlines))
-> [Reference Text] -> m [Reference Inlines]
forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> [a] -> m [b]
mapM ((Text -> m Inlines) -> Reference Text -> m (Reference Inlines)
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Reference a -> f (Reference b)
traverse (Inlines -> m Inlines
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Inlines -> m Inlines) -> (Text -> Inlines) -> Text -> m Inlines
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> Inlines
text)) [Reference Text]
refs
      Pandoc -> m Pandoc
forall a. a -> m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Pandoc -> m Pandoc) -> Pandoc -> m Pandoc
forall a b. (a -> b) -> a -> b
$
        Text -> Inlines -> Pandoc -> Pandoc
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Pandoc -> Pandoc
setMeta Text
"nocite" ([Citation] -> Inlines -> Inlines
cite [Citation {citationId :: Text
citationId = Text
"*"
                                         , citationPrefix :: [Inline]
citationPrefix = []
                                         , citationSuffix :: [Inline]
citationSuffix = []
                                         , citationMode :: CitationMode
citationMode = CitationMode
NormalCitation
                                         , citationNoteNum :: Int
citationNoteNum = Int
0
                                         , citationHash :: Int
citationHash = Int
0}] (Text -> Inlines
str Text
"[@*]")) (Pandoc -> Pandoc) -> Pandoc -> Pandoc
forall a b. (a -> b) -> a -> b
$
        Text -> [MetaValue] -> Pandoc -> Pandoc
forall a b. (HasMeta a, ToMetaValue b) => Text -> b -> a -> a
forall b. ToMetaValue b => Text -> b -> Pandoc -> Pandoc
setMeta Text
"references" ((Reference Inlines -> MetaValue)
-> [Reference Inlines] -> [MetaValue]
forall a b. (a -> b) -> [a] -> [b]
map Reference Inlines -> MetaValue
referenceToMetaValue [Reference Inlines]
refs') (Pandoc -> Pandoc) -> Pandoc -> Pandoc
forall a b. (a -> b) -> a -> b
$
        Blocks -> Pandoc
B.doc Blocks
forall a. Monoid a => a
mempty
    Left PandocError
e       -> PandocError -> m Pandoc
forall a. PandocError -> m a
forall e (m :: * -> *) a. MonadError e m => e -> m a
throwError PandocError
e
type RISParser m = ParsecT Sources () m
risLine :: PandocMonad m => RISParser m (Text, Text)
risLine :: forall (m :: * -> *). PandocMonad m => RISParser m (Text, Text)
risLine = do
  Text
key <- String -> Text
T.pack (String -> Text)
-> ParsecT Sources () m String -> ParsecT Sources () m Text
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> ParsecT Sources () m Char -> ParsecT Sources () m String
forall s (m :: * -> *) t u a.
Stream s m t =>
Int -> ParsecT s u m a -> ParsecT s u m [a]
count Int
2 ((Char -> Bool) -> ParsecT Sources () m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
(Char -> Bool) -> ParsecT s u m Char
satisfy (\Char
c -> Char -> Bool
isAsciiUpper Char
c Bool -> Bool -> Bool
|| Char -> Bool
isDigit Char
c))
  String
_ <- ParsecT Sources () m Char -> ParsecT Sources () m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources () m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
  Char -> ParsecT Sources () m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-'
  Text
val <- (ParsecT Sources () m Char -> ParsecT Sources () m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources () m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar ParsecT Sources () m String
-> ParsecT Sources () m Text -> ParsecT Sources () m Text
forall a b.
ParsecT Sources () m a
-> ParsecT Sources () m b -> ParsecT Sources () m b
forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b
*> ParsecT Sources () m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine) ParsecT Sources () m Text
-> ParsecT Sources () m Text -> ParsecT Sources () m Text
forall s u (m :: * -> *) a.
ParsecT s u m a -> ParsecT s u m a -> ParsecT s u m a
<|> Text
forall a. Monoid a => a
mempty Text -> ParsecT Sources () m Char -> ParsecT Sources () m Text
forall a b. a -> ParsecT Sources () m b -> ParsecT Sources () m a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ ParsecT Sources () m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m Char
newline
  (Text, Text) -> RISParser m (Text, Text)
forall a. a -> ParsecT Sources () m a
forall (m :: * -> *) a. Monad m => a -> m a
return (Text
key, Text -> Text
T.strip Text
val)
risSeparator :: PandocMonad m => RISParser m ()
risSeparator :: forall (m :: * -> *). PandocMonad m => RISParser m ()
risSeparator = do
  ParsecT Sources () m String -> ParsecT Sources () m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m a
try (ParsecT Sources () m String -> ParsecT Sources () m String)
-> ParsecT Sources () m String -> ParsecT Sources () m String
forall a b. (a -> b) -> a -> b
$ String -> ParsecT Sources () m String
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
String -> ParsecT s u m String
string String
"ER"
  String
_ <- ParsecT Sources () m Char -> ParsecT Sources () m String
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many1 ParsecT Sources () m Char
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Char
spaceChar
  Char -> ParsecT Sources () m Char
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
Char -> ParsecT s u m Char
char Char
'-'
  Text
_ <- ParsecT Sources () m Text
forall (m :: * -> *) st. Monad m => ParsecT Sources st m Text
anyLine
  ParsecT Sources () m Text -> RISParser m ()
forall s (m :: * -> *) t u a.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m ()
optional ParsecT Sources () m Text
forall s (m :: * -> *) st.
(Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s st m Text
blanklines
risRecord :: PandocMonad m => RISParser m [(Text, Text)]
risRecord :: forall (m :: * -> *). PandocMonad m => RISParser m [(Text, Text)]
risRecord = ParsecT Sources () m (Text, Text)
-> ParsecT Sources () m () -> ParsecT Sources () m [(Text, Text)]
forall s (m :: * -> *) t u a end.
Stream s m t =>
ParsecT s u m a -> ParsecT s u m end -> ParsecT s u m [a]
manyTill ParsecT Sources () m (Text, Text)
forall (m :: * -> *). PandocMonad m => RISParser m (Text, Text)
risLine ParsecT Sources () m ()
forall (m :: * -> *). PandocMonad m => RISParser m ()
risSeparator
risRecordToReference :: [(Text, Text)] -> Reference Text
risRecordToReference :: [(Text, Text)] -> Reference Text
risRecordToReference [(Text, Text)]
keys = Reference Text -> Reference Text
forall {a}. Reference a -> Reference a
addId (Reference Text -> Reference Text)
-> Reference Text -> Reference Text
forall a b. (a -> b) -> a -> b
$ ((Text, Text) -> Reference Text -> Reference Text)
-> Reference Text -> [(Text, Text)] -> Reference Text
forall a b. (a -> b -> b) -> b -> [a] -> b
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (Text, Text) -> Reference Text -> Reference Text
forall {a}.
(Eq a, IsString a) =>
(a, Text) -> Reference Text -> Reference Text
go Reference Text
forall {a}. Reference a
defref [(Text, Text)]
keys
 where
   go :: (a, Text) -> Reference Text -> Reference Text
go (a
key, Text
val) =
     case a
key of
       a
"TY" -> \Reference Text
ref -> Reference Text
ref{ referenceType =
          fromMaybe "misc" (M.lookup val risTypes) }
       a
"ID" -> \Reference Text
ref -> Reference Text
ref{ referenceId = ItemId val }
       a
"VL" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"volume" Text
val
       a
"KW" -> \Reference Text
ref ->
         Reference Text
ref{ referenceVariables =
               M.alter (\Maybe (Val Text)
x -> case Maybe (Val Text)
x of
                           Maybe (Val Text)
Nothing -> Val Text -> Maybe (Val Text)
forall a. a -> Maybe a
Just (Val Text -> Maybe (Val Text)) -> Val Text -> Maybe (Val Text)
forall a b. (a -> b) -> a -> b
$ Text -> Val Text
forall a. Text -> Val a
TextVal Text
val
                           Just (TextVal Text
kws)
                                   -> Val Text -> Maybe (Val Text)
forall a. a -> Maybe a
Just (Text -> Val Text
forall a. Text -> Val a
TextVal (Text
kws Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
", " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
val))
                           Maybe (Val Text)
_ -> Maybe (Val Text)
x)
               "keyword"
               (referenceVariables ref) }
       a
"PB" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"publisher" Text
val
       a
"PP" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"publisher-place" Text
val
       a
"DO" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"DOI" Text
val
       a
"SP" -> \Reference Text
ref ->
         case Variable -> Map Variable (Val Text) -> Maybe (Val Text)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Variable
"page" (Reference Text -> Map Variable (Val Text)
forall a. Reference a -> Map Variable (Val a)
referenceVariables Reference Text
ref) of
           Maybe (Val Text)
Nothing -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"page" Text
val Reference Text
ref
           Just (FancyVal Text
eg) -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"page" (Text
val Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
eg) Reference Text
ref
           Maybe (Val Text)
_ -> Reference Text
ref
       a
"EP" -> \Reference Text
ref ->
         case Variable -> Map Variable (Val Text) -> Maybe (Val Text)
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Variable
"page" (Reference Text -> Map Variable (Val Text)
forall a. Reference a -> Map Variable (Val a)
referenceVariables Reference Text
ref) of
           Maybe (Val Text)
Nothing -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"page" (Text
"-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
val) Reference Text
ref
           Just (FancyVal Text
eg) -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"page" (Text
val Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"-" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
eg) Reference Text
ref
           Maybe (Val Text)
_ -> Reference Text
ref
       a
"AU" -> Variable -> Text -> Reference Text -> Reference Text
forall {a}. Variable -> Text -> Reference a -> Reference a
addName Variable
"author" Text
val
       a
"A1" -> Variable -> Text -> Reference Text -> Reference Text
forall {a}. Variable -> Text -> Reference a -> Reference a
addName Variable
"author" Text
val
       a
"ED" -> Variable -> Text -> Reference Text -> Reference Text
forall {a}. Variable -> Text -> Reference a -> Reference a
addName Variable
"editor" Text
val
       a
"A2" -> Variable -> Text -> Reference Text -> Reference Text
forall {a}. Variable -> Text -> Reference a -> Reference a
addName Variable
"editor" Text
val
       a
"TI" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"title" Text
val
       a
"T1" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"title" Text
val
       a
"CT" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"title" Text
val
       a
"BT" -> \Reference Text
ref ->
         if Reference Text -> Text
forall a. Reference a -> Text
referenceType Reference Text
ref Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"book"
            then Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"title" Text
val Reference Text
ref
            else Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"container-title" Text
val Reference Text
ref
       a
"JO" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"container-title" Text
val
       a
"JF" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"container-title" Text
val
       a
"T2" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"container-title" Text
val
       a
"ET" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"edition" Text
val
       a
"NV" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"number-of-volumes" Text
val
       a
"AB" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"abstract" Text
val
       a
"PY" -> Variable -> Text -> Reference Text -> Reference Text
forall {a}. Variable -> Text -> Reference a -> Reference a
addYear Variable
"issued" Text
val
       a
"Y1" -> Variable -> Text -> Reference Text -> Reference Text
forall {a}. Variable -> Text -> Reference a -> Reference a
addYear Variable
"issued" Text
val
       a
"IS" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"issue" Text
val
       a
"SN" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"ISSN" Text
val
       a
"LA" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"language" Text
val
       a
"UR" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"url" Text
val
       a
"LK" -> Text -> Text -> Reference Text -> Reference Text
forall {a}. Text -> a -> Reference a -> Reference a
addVar Text
"url" Text
val
       a
_ -> Reference Text -> Reference Text
forall a. a -> a
id 
   addVar :: Text -> a -> Reference a -> Reference a
addVar Text
k a
v Reference a
r = Reference a
r{ referenceVariables =
                       M.insert (toVariable k) (FancyVal v)
                       (referenceVariables r) }
   addName :: Variable -> Text -> Reference a -> Reference a
addName Variable
k Text
v Reference a
r =
     let new :: [Name]
new = NameOpts -> [Inline] -> [Name]
forall (m :: * -> *). Monad m => NameOpts -> [Inline] -> m Name
toName NameOpts{ nameOptsPrefixIsNonDroppingParticle :: Bool
nameOptsPrefixIsNonDroppingParticle = Bool
False
                              , nameOptsUseJuniorComma :: Bool
nameOptsUseJuniorComma = Bool
False }
                ([Inline] -> [Name]) -> (Text -> [Inline]) -> Text -> [Name]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Inlines -> [Inline]
forall a. Many a -> [a]
B.toList (Inlines -> [Inline]) -> (Text -> Inlines) -> Text -> [Inline]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.  Text -> Inlines
B.text (Text -> [Name]) -> Text -> [Name]
forall a b. (a -> b) -> a -> b
$ Text
v
         f :: Maybe (Val a) -> Maybe (Val a)
f Maybe (Val a)
Nothing   = Val a -> Maybe (Val a)
forall a. a -> Maybe a
Just ([Name] -> Val a
forall a. [Name] -> Val a
NamesVal [Name]
new)
         f (Just (NamesVal [Name]
ns)) = Val a -> Maybe (Val a)
forall a. a -> Maybe a
Just ([Name] -> Val a
forall a. [Name] -> Val a
NamesVal ([Name]
new [Name] -> [Name] -> [Name]
forall a. [a] -> [a] -> [a]
++ [Name]
ns))
         f (Just Val a
x) = Val a -> Maybe (Val a)
forall a. a -> Maybe a
Just Val a
x
      in Reference a
r{ referenceVariables =
              M.alter f k (referenceVariables r) }
   addYear :: Variable -> Text -> Reference a -> Reference a
addYear Variable
k Text
v Reference a
r =
     let d :: Val a
d = Date -> Val a
forall a. Date -> Val a
DateVal (Date -> Val a) -> Date -> Val a
forall a b. (a -> b) -> a -> b
$
              case String -> Maybe Int
forall a. Read a => String -> Maybe a
readMay (Text -> String
T.unpack Text
v) of
                Maybe Int
Nothing ->
                  Date { dateParts :: [DateParts]
dateParts = []
                       , dateCirca :: Bool
dateCirca = Bool
False
                       , dateSeason :: Maybe Int
dateSeason = Maybe Int
forall a. Maybe a
Nothing
                       , dateLiteral :: Maybe Text
dateLiteral = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
v }
                Just Int
y ->
                  Date { dateParts :: [DateParts]
dateParts = [[Int] -> DateParts
DateParts [Int
y]]
                       , dateCirca :: Bool
dateCirca = Bool
False
                       , dateSeason :: Maybe Int
dateSeason = Maybe Int
forall a. Maybe a
Nothing
                       , dateLiteral :: Maybe Text
dateLiteral = Maybe Text
forall a. Maybe a
Nothing }
      in Reference a
r{ referenceVariables = M.insert k d (referenceVariables r) }
   defref :: Reference a
defref = Reference{
       referenceId :: ItemId
referenceId = ItemId
forall a. Monoid a => a
mempty
     , referenceType :: Text
referenceType = Text
forall a. Monoid a => a
mempty
     , referenceDisambiguation :: Maybe DisambiguationData
referenceDisambiguation = Maybe DisambiguationData
forall a. Maybe a
Nothing
     , referenceVariables :: Map Variable (Val a)
referenceVariables = Map Variable (Val a)
forall a. Monoid a => a
mempty }
   addId :: Reference a -> Reference a
addId Reference a
rec =
     if Reference a -> ItemId
forall a. Reference a -> ItemId
referenceId Reference a
rec ItemId -> ItemId -> Bool
forall a. Eq a => a -> a -> Bool
== ItemId
forall a. Monoid a => a
mempty
        then Reference a
rec{ referenceId = ItemId (authors <> pubdate) }
        else Reference a
rec
   authors :: Text
authors = Text -> [Text] -> Text
T.intercalate Text
"_" ([Text] -> Text) -> [Text] -> Text
forall a b. (a -> b) -> a -> b
$
               [(Char -> Bool) -> Text -> Text
T.takeWhile (\Char
c -> Char
c Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
',' Bool -> Bool -> Bool
&& Bool -> Bool
not (Char -> Bool
isSpace Char
c)) Text
n
                 | (Text
k, Text
n) <- [(Text, Text)]
keys, Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"AU" Bool -> Bool -> Bool
|| Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"A1"]
   pubdate :: Text
pubdate = [Text] -> Text
forall a. Monoid a => [a] -> a
mconcat [Text
"_" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
d | (Text
k, Text
d) <- [(Text, Text)]
keys, Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"PY" Bool -> Bool -> Bool
|| Text
k Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
"Y1"]
risReferences :: PandocMonad m => RISParser m [Reference Text]
risReferences :: forall (m :: * -> *). PandocMonad m => RISParser m [Reference Text]
risReferences = do
  [[(Text, Text)]]
recs <- ParsecT Sources () m [(Text, Text)]
-> ParsecT Sources () m [[(Text, Text)]]
forall s u (m :: * -> *) a. ParsecT s u m a -> ParsecT s u m [a]
many ParsecT Sources () m [(Text, Text)]
forall (m :: * -> *). PandocMonad m => RISParser m [(Text, Text)]
risRecord
  ParsecT Sources () m ()
forall (m :: * -> *) s u.
(Monad m, Stream s m Char, UpdateSourcePos s Char) =>
ParsecT s u m ()
spaces
  ParsecT Sources () m ()
forall s (m :: * -> *) t u.
(Stream s m t, Show t) =>
ParsecT s u m ()
eof
  [Reference Text] -> RISParser m [Reference Text]
forall a. a -> ParsecT Sources () m a
forall (m :: * -> *) a. Monad m => a -> m a
return ([Reference Text] -> RISParser m [Reference Text])
-> [Reference Text] -> RISParser m [Reference Text]
forall a b. (a -> b) -> a -> b
$ [Reference Text] -> [Reference Text]
fixDuplicateIds ([Reference Text] -> [Reference Text])
-> [Reference Text] -> [Reference Text]
forall a b. (a -> b) -> a -> b
$ ([(Text, Text)] -> Reference Text)
-> [[(Text, Text)]] -> [Reference Text]
forall a b. (a -> b) -> [a] -> [b]
map [(Text, Text)] -> Reference Text
risRecordToReference [[(Text, Text)]]
recs
fixDuplicateIds :: [Reference Text] -> [Reference Text]
fixDuplicateIds :: [Reference Text] -> [Reference Text]
fixDuplicateIds = [Reference Text] -> [Reference Text]
forall a. [a] -> [a]
reverse ([Reference Text] -> [Reference Text])
-> ([Reference Text] -> [Reference Text])
-> [Reference Text]
-> [Reference Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Map ItemId Int, [Reference Text]) -> [Reference Text]
forall a b. (a, b) -> b
snd ((Map ItemId Int, [Reference Text]) -> [Reference Text])
-> ([Reference Text] -> (Map ItemId Int, [Reference Text]))
-> [Reference Text]
-> [Reference Text]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Map ItemId Int, [Reference Text])
 -> Reference Text -> (Map ItemId Int, [Reference Text]))
-> (Map ItemId Int, [Reference Text])
-> [Reference Text]
-> (Map ItemId Int, [Reference Text])
forall b a. (b -> a -> b) -> b -> [a] -> b
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Map ItemId Int, [Reference Text])
-> Reference Text -> (Map ItemId Int, [Reference Text])
forall {a}.
(Map ItemId Int, [Reference a])
-> Reference a -> (Map ItemId Int, [Reference a])
go (Map ItemId Int
forall a. Monoid a => a
mempty, [])
 where
   go :: (Map ItemId Int, [Reference a])
-> Reference a -> (Map ItemId Int, [Reference a])
go (Map ItemId Int
ids_seen, [Reference a]
refs) Reference a
ref =
     case ItemId -> Map ItemId Int -> Maybe Int
forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Reference a -> ItemId
forall a. Reference a -> ItemId
referenceId Reference a
ref) Map ItemId Int
ids_seen of
       Maybe Int
Nothing -> (ItemId -> Int -> Map ItemId Int -> Map ItemId Int
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (Reference a -> ItemId
forall a. Reference a -> ItemId
referenceId Reference a
ref) (Char -> Int
ord Char
'a') Map ItemId Int
ids_seen, Reference a
refReference a -> [Reference a] -> [Reference a]
forall a. a -> [a] -> [a]
:[Reference a]
refs)
       Just Int
n  -> (ItemId -> Int -> Map ItemId Int -> Map ItemId Int
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert (Reference a -> ItemId
forall a. Reference a -> ItemId
referenceId Reference a
ref) (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1) Map ItemId Int
ids_seen,
                     Reference a
ref{ referenceId =
                          ItemId . (<> T.singleton (chr n)) . unItemId $
                           referenceId ref }
                    Reference a -> [Reference a] -> [Reference a]
forall a. a -> [a] -> [a]
: [Reference a]
refs)
risTypes :: M.Map Text Text
risTypes :: Map Text Text
risTypes = [(Text, Text)] -> Map Text Text
forall k a. Ord k => [(k, a)] -> Map k a
M.fromList
    [ (Text
"ABST", Text
"article")
    , (Text
"ADVS", Text
"motion-picture")
    , (Text
"AGGR", Text
"dataset")
    , (Text
"ANCIENT", Text
"book")
    , (Text
"ART", Text
"graphic")
    , (Text
"BILL", Text
"bill")
    , (Text
"BLOG", Text
"post-weblog")
    , (Text
"BOOK", Text
"book")
    , (Text
"CASE", Text
"legal_case")
    , (Text
"CHAP", Text
"chapter")
    , (Text
"CHART", Text
"graphic")
    , (Text
"CLSWK", Text
"book")
    , (Text
"COMP", Text
"program")
    , (Text
"CONF", Text
"paper-conference")
    , (Text
"CPAPER", Text
"paper-conference")
    , (Text
"CTLG", Text
"catalog")
    , (Text
"DATA", Text
"dataset")
    , (Text
"DBASE", Text
"dataset")
    , (Text
"DICT", Text
"book")
    , (Text
"EBOOK", Text
"book")
    , (Text
"ECHAP", Text
"chapter")
    , (Text
"EDBOOK", Text
"book")
    , (Text
"EJOUR", Text
"article")
    , (Text
"WEB", Text
"webpage")
    , (Text
"ENCYC", Text
"entry-encyclopedia")
    , (Text
"EQUA", Text
"figure")
    , (Text
"FIGURE", Text
"figure")
    , (Text
"GEN", Text
"entry")
    , (Text
"GOVDOC", Text
"report")
    , (Text
"GRANT", Text
"report")
    , (Text
"HEAR", Text
"report")
    , (Text
"ICOMM", Text
"personal_communication")
    , (Text
"INPR", Text
"article-journal")
    , (Text
"JFULL", Text
"article-journal")
    , (Text
"JOUR", Text
"article-journal")
    , (Text
"LEGAL", Text
"legal_case")
    , (Text
"MANSCPT", Text
"manuscript")
    , (Text
"MAP", Text
"map")
    , (Text
"MGZN", Text
"article-magazine")
    , (Text
"MPCT", Text
"motion-picture")
    , (Text
"MULTI", Text
"webpage")
    , (Text
"MUSIC", Text
"musical_score")
    , (Text
"NEWS", Text
"article-newspaper")
    , (Text
"PAMP", Text
"pamphlet")
    , (Text
"PAT", Text
"patent")
    , (Text
"PCOMM", Text
"personal_communication")
    , (Text
"RPRT", Text
"report")
    , (Text
"SER", Text
"article")
    , (Text
"SLIDE", Text
"graphic")
    , (Text
"SOUND", Text
"musical_score")
    , (Text
"STAND", Text
"report")
    , (Text
"STAT", Text
"legislation")
    , (Text
"THES", Text
"thesis")
    , (Text
"UNBILL", Text
"bill")
    , (Text
"UNPB", Text
"unpublished")
    , (Text
"VIDEO", Text
"graphic") ]