{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedStrings #-}
module Text.Pandoc.Translations.Types (
Term(..)
, Translations
, lookupTerm
)
where
import Data.Aeson.Types (Value(..), FromJSON(..))
import qualified Data.Aeson.Types as Aeson
import qualified Data.Map as M
import qualified Data.Text as T
import GHC.Generics (Generic)
import Text.Pandoc.Shared (safeRead)
data Term =
Abstract
| Appendix
| Bibliography
| Cc
| Chapter
| Contents
| Encl
| Figure
| Glossary
| Index
| Listing
| ListOfFigures
| ListOfTables
| Page
| Part
| Preface
| Proof
| References
| See
| SeeAlso
| Table
| To
deriving (Int -> Term -> ShowS
[Term] -> ShowS
Term -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Term] -> ShowS
$cshowList :: [Term] -> ShowS
show :: Term -> String
$cshow :: Term -> String
showsPrec :: Int -> Term -> ShowS
$cshowsPrec :: Int -> Term -> ShowS
Show, Term -> Term -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Term -> Term -> Bool
$c/= :: Term -> Term -> Bool
== :: Term -> Term -> Bool
$c== :: Term -> Term -> Bool
Eq, Eq Term
Term -> Term -> Bool
Term -> Term -> Ordering
Term -> Term -> Term
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Term -> Term -> Term
$cmin :: Term -> Term -> Term
max :: Term -> Term -> Term
$cmax :: Term -> Term -> Term
>= :: Term -> Term -> Bool
$c>= :: Term -> Term -> Bool
> :: Term -> Term -> Bool
$c> :: Term -> Term -> Bool
<= :: Term -> Term -> Bool
$c<= :: Term -> Term -> Bool
< :: Term -> Term -> Bool
$c< :: Term -> Term -> Bool
compare :: Term -> Term -> Ordering
$ccompare :: Term -> Term -> Ordering
Ord, forall x. Rep Term x -> Term
forall x. Term -> Rep Term x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Term x -> Term
$cfrom :: forall x. Term -> Rep Term x
Generic, Int -> Term
Term -> Int
Term -> [Term]
Term -> Term
Term -> Term -> [Term]
Term -> Term -> Term -> [Term]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
enumFromThenTo :: Term -> Term -> Term -> [Term]
$cenumFromThenTo :: Term -> Term -> Term -> [Term]
enumFromTo :: Term -> Term -> [Term]
$cenumFromTo :: Term -> Term -> [Term]
enumFromThen :: Term -> Term -> [Term]
$cenumFromThen :: Term -> Term -> [Term]
enumFrom :: Term -> [Term]
$cenumFrom :: Term -> [Term]
fromEnum :: Term -> Int
$cfromEnum :: Term -> Int
toEnum :: Int -> Term
$ctoEnum :: Int -> Term
pred :: Term -> Term
$cpred :: Term -> Term
succ :: Term -> Term
$csucc :: Term -> Term
Enum, ReadPrec [Term]
ReadPrec Term
Int -> ReadS Term
ReadS [Term]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Term]
$creadListPrec :: ReadPrec [Term]
readPrec :: ReadPrec Term
$creadPrec :: ReadPrec Term
readList :: ReadS [Term]
$creadList :: ReadS [Term]
readsPrec :: Int -> ReadS Term
$creadsPrec :: Int -> ReadS Term
Read)
newtype Translations = Translations (M.Map Term T.Text)
deriving (Int -> Translations -> ShowS
[Translations] -> ShowS
Translations -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Translations] -> ShowS
$cshowList :: [Translations] -> ShowS
show :: Translations -> String
$cshow :: Translations -> String
showsPrec :: Int -> Translations -> ShowS
$cshowsPrec :: Int -> Translations -> ShowS
Show, forall x. Rep Translations x -> Translations
forall x. Translations -> Rep Translations x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Translations x -> Translations
$cfrom :: forall x. Translations -> Rep Translations x
Generic, NonEmpty Translations -> Translations
Translations -> Translations -> Translations
forall b. Integral b => b -> Translations -> Translations
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: forall b. Integral b => b -> Translations -> Translations
$cstimes :: forall b. Integral b => b -> Translations -> Translations
sconcat :: NonEmpty Translations -> Translations
$csconcat :: NonEmpty Translations -> Translations
<> :: Translations -> Translations -> Translations
$c<> :: Translations -> Translations -> Translations
Semigroup, Semigroup Translations
Translations
[Translations] -> Translations
Translations -> Translations -> Translations
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [Translations] -> Translations
$cmconcat :: [Translations] -> Translations
mappend :: Translations -> Translations -> Translations
$cmappend :: Translations -> Translations -> Translations
mempty :: Translations
$cmempty :: Translations
Monoid)
instance FromJSON Term where
parseJSON :: Value -> Parser Term
parseJSON (String Text
t) = case forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead Text
t of
Just Term
t' -> forall (f :: * -> *) a. Applicative f => a -> f a
pure Term
t'
Maybe Term
Nothing -> forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail forall a b. (a -> b) -> a -> b
$ String
"Invalid Term name " forall a. [a] -> [a] -> [a]
++
forall a. Show a => a -> String
show Text
t
parseJSON Value
invalid = forall a. String -> Value -> Parser a
Aeson.typeMismatch String
"Term" Value
invalid
instance FromJSON Translations where
parseJSON :: Value -> Parser Translations
parseJSON o :: Value
o@(Object{}) = do
[(Term, Text)]
xs <- forall a. FromJSON a => Value -> Parser a
parseJSON Value
o forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall (t :: * -> *) (m :: * -> *) a b.
(Traversable t, Monad m) =>
(a -> m b) -> t a -> m (t b)
mapM forall {a}. Read a => (Text, Value) -> Parser (a, Text)
addItem forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k a. Map k a -> [(k, a)]
M.toList
forall (m :: * -> *) a. Monad m => a -> m a
return forall a b. (a -> b) -> a -> b
$ Map Term Text -> Translations
Translations (forall k a. Ord k => [(k, a)] -> Map k a
M.fromList [(Term, Text)]
xs)
where addItem :: (Text, Value) -> Parser (a, Text)
addItem (Text
k,Value
v) =
case forall (m :: * -> *) a. (MonadPlus m, Read a) => Text -> m a
safeRead Text
k of
Maybe a
Nothing -> forall (m :: * -> *) a. MonadFail m => String -> m a
Prelude.fail forall a b. (a -> b) -> a -> b
$ String
"Invalid Term name " forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Text
k
Just a
t ->
case Value
v of
(String Text
s) -> forall (m :: * -> *) a. Monad m => a -> m a
return (a
t, Text -> Text
T.strip Text
s)
Value
inv -> forall a. String -> Value -> Parser a
Aeson.typeMismatch String
"String" Value
inv
parseJSON Value
invalid = forall a. String -> Value -> Parser a
Aeson.typeMismatch String
"Translations" Value
invalid
lookupTerm :: Term -> Translations -> Maybe T.Text
lookupTerm :: Term -> Translations -> Maybe Text
lookupTerm Term
t (Translations Map Term Text
tm) = forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup Term
t Map Term Text
tm