{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Text.Pandoc.Citeproc.Data
  (biblatexStringMap)
where
import Data.FileEmbed
import Data.ByteString (ByteString)
import qualified Data.Map as M
import qualified Data.Text.Encoding as TE
import qualified Data.Text as T
import Data.Text (Text)
import Text.Pandoc.Citeproc.Util (toIETF)
import Citeproc (Lang(..), parseLang)
biblatexLocalizations :: [(FilePath, ByteString)]
biblatexLocalizations :: [(FilePath, ByteString)]
biblatexLocalizations = $(embedDir "citeproc/biblatex-localization")
biblatexStringMap :: M.Map Text (M.Map Text (Text, Text))
biblatexStringMap :: Map Text (Map Text (Text, Text))
biblatexStringMap = ((FilePath, ByteString)
 -> Map Text (Map Text (Text, Text))
 -> Map Text (Map Text (Text, Text)))
-> Map Text (Map Text (Text, Text))
-> [(FilePath, ByteString)]
-> Map Text (Map Text (Text, Text))
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr (FilePath, ByteString)
-> Map Text (Map Text (Text, Text))
-> Map Text (Map Text (Text, Text))
go Map Text (Map Text (Text, Text))
forall a. Monoid a => a
mempty [(FilePath, ByteString)]
biblatexLocalizations
 where
  go :: (FilePath, ByteString)
-> Map Text (Map Text (Text, Text))
-> Map Text (Map Text (Text, Text))
go (FilePath
fp, ByteString
bs) =
    let Lang Text
lang Maybe Text
_ = Text -> Lang
parseLang (Text -> Text
toIETF (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ (Char -> Bool) -> Text -> Text
T.takeWhile (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
/= Char
'.') (Text -> Text) -> Text -> Text
forall a b. (a -> b) -> a -> b
$ FilePath -> Text
T.pack FilePath
fp)
        ls :: [Text]
ls = Text -> [Text]
T.lines (Text -> [Text]) -> Text -> [Text]
forall a b. (a -> b) -> a -> b
$ ByteString -> Text
TE.decodeUtf8 ByteString
bs
     in if [Text] -> Int
forall (t :: * -> *) a. Foldable t => t a -> Int
length [Text]
ls Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
4
           then Text
-> Map Text (Text, Text)
-> Map Text (Map Text (Text, Text))
-> Map Text (Map Text (Text, Text))
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert Text
lang ([[Text]] -> Map Text (Text, Text)
toStringMap ([[Text]] -> Map Text (Text, Text))
-> [[Text]] -> Map Text (Text, Text)
forall a b. (a -> b) -> a -> b
$ (Text -> [Text]) -> [Text] -> [[Text]]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Text -> [Text]
T.splitOn Text
"|") [Text]
ls)
           else Map Text (Map Text (Text, Text))
-> Map Text (Map Text (Text, Text))
forall a. a -> a
id
  toStringMap :: [[Text]] -> Map Text (Text, Text)
toStringMap = ([Text] -> Map Text (Text, Text) -> Map Text (Text, Text))
-> Map Text (Text, Text) -> [[Text]] -> Map Text (Text, Text)
forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr [Text] -> Map Text (Text, Text) -> Map Text (Text, Text)
forall b. Ord b => [b] -> Map b (b, b) -> Map b (b, b)
go' Map Text (Text, Text)
forall a. Monoid a => a
mempty
  go' :: [b] -> Map b (b, b) -> Map b (b, b)
go' [b
term, b
x, b
y] = b -> (b, b) -> Map b (b, b) -> Map b (b, b)
forall k a. Ord k => k -> a -> Map k a -> Map k a
M.insert b
term (b
x, b
y)
  go' [b]
_ = Map b (b, b) -> Map b (b, b)
forall a. a -> a
id