{-# LANGUAGE OverloadedStrings   #-}
{-# LANGUAGE ScopedTypeVariables #-}
{- |
   Module      : Text.Pandoc.Writers.LaTeX.Lang
   Copyright   : Copyright (C) 2006-2023 John MacFarlane
   License     : GNU GPL, version 2 or above

   Maintainer  : John MacFarlane <jgm@berkeley.edu>
   Stability   : alpha
   Portability : portable
-}
module Text.Pandoc.Writers.LaTeX.Lang
  ( toBabel
  ) where
import Data.Text (Text)
import Text.Collate.Lang (Lang(..))


-- Takes a list of the constituents of a BCP47 language code and
-- converts it to a Babel language string.
-- http://mirrors.ctan.org/macros/latex/required/babel/base/babel.pdf
-- List of supported languages (slightly outdated):
-- http://tug.ctan.org/language/hyph-utf8/doc/generic/hyph-utf8/hyphenation.pdf
toBabel :: Lang -> Maybe Text
toBabel :: Lang -> Maybe Text
toBabel (Lang Text
"de" Maybe Text
_ (Just Text
"AT") [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
  | Text
"1901" Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars                  = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"austrian"
  | Bool
otherwise                           = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"naustrian"
toBabel (Lang Text
"de" Maybe Text
_ (Just Text
"CH") [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
  | Text
"1901" Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars                  = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"swissgerman"
  | Bool
otherwise                           = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"nswissgerman"
toBabel (Lang Text
"de" Maybe Text
_ Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
  | Text
"1901" Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars                  = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"german"
  | Bool
otherwise                           = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ngerman"
toBabel (Lang Text
"dsb" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_)          = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"lowersorbian"
toBabel (Lang Text
"el" Maybe Text
_ Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
  | Text
"polyton" Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars               = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"polutonikogreek"
toBabel (Lang Text
"en" Maybe Text
_ (Just Text
"AU") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"australian"
toBabel (Lang Text
"en" Maybe Text
_ (Just Text
"CA") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"canadian"
toBabel (Lang Text
"en" Maybe Text
_ (Just Text
"GB") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"british"
toBabel (Lang Text
"en" Maybe Text
_ (Just Text
"NZ") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"newzealand"
toBabel (Lang Text
"en" Maybe Text
_ (Just Text
"UK") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"british"
toBabel (Lang Text
"en" Maybe Text
_ (Just Text
"US") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"american"
toBabel (Lang Text
"fr" Maybe Text
_ (Just Text
"CA") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"canadien"
toBabel (Lang Text
"fra" Maybe Text
_ Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
  | Text
"aca" Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars                   = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"acadian"
toBabel (Lang Text
"grc" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_)          = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"ancientgreek"
toBabel (Lang Text
"hsb" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_)          = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"uppersorbian"
toBabel (Lang Text
"la" Maybe Text
_ Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
  | Text
"x-classic" Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars             = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"classiclatin"
toBabel (Lang Text
"pt" Maybe Text
_ (Just Text
"BR") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"brazilian"
toBabel (Lang Text
"sl" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_)           = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"slovene"
toBabel (Lang Text
"zh" (Just Text
"Hant") (Just Text
"HK") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"chinese-hant-hk"
toBabel (Lang Text
"zh" (Just Text
"Hant") (Just Text
"MO") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"chinese-hant-mo"
toBabel (Lang Text
"zh" (Just Text
"Hans") (Just Text
"HK") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"chinese-hans-hk"
toBabel (Lang Text
"zh" (Just Text
"Hans") (Just Text
"MO") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"chinese-hans-mo"
toBabel (Lang Text
"zh" (Just Text
"Hans") Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"chinese-hans"
toBabel (Lang Text
"zh" (Just Text
"Hant") Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"chinese-hant"
toBabel (Lang Text
"zh" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_)             = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"chinese"
toBabel Lang
x                                 = Lang -> Maybe Text
commonFromBcp47 Lang
x

-- Takes a list of the constituents of a BCP47 language code
-- and converts it to a string shared by Babel and Polyglossia.
-- https://tools.ietf.org/html/bcp47#section-2.1
commonFromBcp47 :: Lang -> Maybe Text
commonFromBcp47 :: Lang -> Maybe Text
commonFromBcp47 (Lang Text
"sr" (Just Text
"Cyrl") Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_)      = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"serbianc"
commonFromBcp47 (Lang Text
"zh" (Just Text
"Latn") Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
  | Text
"pinyin" Text -> [Text] -> Bool
forall a. Eq a => a -> [a] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars                               = Text -> Maybe Text
forall a. a -> Maybe a
Just Text
"pinyin"
commonFromBcp47 (Lang Text
l Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Maybe Text
forall {a} {a}. (Eq a, IsString a, IsString a) => a -> Maybe a
fromIso Text
l
  where
    fromIso :: a -> Maybe a
fromIso a
"af"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"afrikaans"
    fromIso a
"am"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"amharic"
    fromIso a
"ar"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"arabic"
    fromIso a
"as"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"assamese"
    fromIso a
"ast" = a -> Maybe a
forall a. a -> Maybe a
Just a
"asturian"
    fromIso a
"bg"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"bulgarian"
    fromIso a
"bn"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"bengali"
    fromIso a
"bo"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"tibetan"
    fromIso a
"br"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"breton"
    fromIso a
"ca"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"catalan"
    fromIso a
"cy"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"welsh"
    fromIso a
"cs"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"czech"
    fromIso a
"cop" = a -> Maybe a
forall a. a -> Maybe a
Just a
"coptic"
    fromIso a
"da"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"danish"
    fromIso a
"dv"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"divehi"
    fromIso a
"el"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"greek"
    fromIso a
"en"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"english"
    fromIso a
"eo"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"esperanto"
    fromIso a
"es"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"spanish"
    fromIso a
"et"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"estonian"
    fromIso a
"eu"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"basque"
    fromIso a
"fa"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"persian"
    fromIso a
"fi"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"finnish"
    fromIso a
"fr"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"french"
    fromIso a
"fur" = a -> Maybe a
forall a. a -> Maybe a
Just a
"friulan"
    fromIso a
"ga"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"irish"
    fromIso a
"gd"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"scottish"
    fromIso a
"gez" = a -> Maybe a
forall a. a -> Maybe a
Just a
"ethiopic"
    fromIso a
"gl"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"galician"
    fromIso a
"gu"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"gujarati"
    fromIso a
"he"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"hebrew"
    fromIso a
"hi"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"hindi"
    fromIso a
"hr"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"croatian"
    fromIso a
"hu"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"magyar"
    fromIso a
"hy"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"armenian"
    fromIso a
"ia"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"interlingua"
    fromIso a
"id"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"indonesian"
    fromIso a
"ie"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"interlingua"
    fromIso a
"is"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"icelandic"
    fromIso a
"it"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"italian"
    fromIso a
"ja"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"japanese"
    fromIso a
"km"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"khmer"
    fromIso a
"kmr" = a -> Maybe a
forall a. a -> Maybe a
Just a
"kurmanji"
    fromIso a
"kn"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"kannada"
    fromIso a
"ko"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"korean"
    fromIso a
"la"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"latin"
    fromIso a
"lo"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"lao"
    fromIso a
"lt"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"lithuanian"
    fromIso a
"lv"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"latvian"
    fromIso a
"ml"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"malayalam"
    fromIso a
"mn"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"mongolian"
    fromIso a
"mr"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"marathi"
    fromIso a
"nb"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"norsk"
    fromIso a
"nl"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"dutch"
    fromIso a
"nn"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"nynorsk"
    fromIso a
"no"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"norsk"
    fromIso a
"nqo" = a -> Maybe a
forall a. a -> Maybe a
Just a
"nko"
    fromIso a
"oc"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"occitan"
    fromIso a
"or"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"oriya"
    fromIso a
"pa"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"punjabi"
    fromIso a
"pl"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"polish"
    fromIso a
"pms" = a -> Maybe a
forall a. a -> Maybe a
Just a
"piedmontese"
    fromIso a
"pt"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"portuguese"
    fromIso a
"rm"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"romansh"
    fromIso a
"ro"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"romanian"
    fromIso a
"ru"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"russian"
    fromIso a
"sa"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"sanskrit"
    fromIso a
"se"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"samin"
    fromIso a
"sk"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"slovak"
    fromIso a
"sq"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"albanian"
    fromIso a
"sr"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"serbian"
    fromIso a
"sv"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"swedish"
    fromIso a
"syr" = a -> Maybe a
forall a. a -> Maybe a
Just a
"syriac"
    fromIso a
"ta"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"tamil"
    fromIso a
"te"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"telugu"
    fromIso a
"th"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"thai"
    fromIso a
"ti"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"ethiopic"
    fromIso a
"tk"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"turkmen"
    fromIso a
"tr"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"turkish"
    fromIso a
"uk"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"ukrainian"
    fromIso a
"ur"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"urdu"
    fromIso a
"vi"  = a -> Maybe a
forall a. a -> Maybe a
Just a
"vietnamese"
    fromIso a
_     = Maybe a
forall a. Maybe a
Nothing