module Text.Pandoc.Translations (
Term(..)
, Translations
, lookupTerm
, readTranslations
)
where
import Data.Aeson.Types (typeMismatch)
import qualified Data.HashMap.Strict as HM
import qualified Data.Map as M
import Data.Text as T
import Data.Yaml as Yaml
import GHC.Generics (Generic)
import Text.Pandoc.Shared (safeRead)
import qualified Text.Pandoc.UTF8 as UTF8
data Term =
Preface
| References
| Abstract
| Bibliography
| Chapter
| Appendix
| Contents
| ListOfFigures
| ListOfTables
| Index
| Figure
| Table
| Part
| Page
| See
| SeeAlso
| Encl
| Cc
| To
| Proof
| Glossary
| Listing
deriving (Show, Eq, Ord, Generic, Enum, Read)
newtype Translations = Translations (M.Map Term String)
deriving (Show, Generic, Monoid)
instance FromJSON Term where
parseJSON (String t) = case safeRead (T.unpack t) of
Just t' -> pure t'
Nothing -> fail $ "Invalid Term name " ++
show t
parseJSON invalid = typeMismatch "Term" invalid
instance FromJSON Translations where
parseJSON (Object hm) = do
xs <- mapM addItem (HM.toList hm)
return $ Translations (M.fromList xs)
where addItem (k,v) =
case safeRead (T.unpack k) of
Nothing -> fail $ "Invalid Term name " ++ show k
Just t ->
case v of
(String s) -> return (t, T.unpack $ T.strip s)
inv -> typeMismatch "String" inv
parseJSON invalid = typeMismatch "Translations" invalid
lookupTerm :: Term -> Translations -> Maybe String
lookupTerm t (Translations tm) = M.lookup t tm
readTranslations :: String -> Either String Translations
readTranslations s =
case Yaml.decodeEither' $ UTF8.fromString s of
Left err' -> Left $ prettyPrintParseException err'
Right t -> Right t