{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Text.Pandoc.Writers.LaTeX.Lang
( toPolyglossiaEnv,
toPolyglossia,
toBabel
) where
import Data.Text (Text)
import Text.Collate.Lang (Lang(..))
toPolyglossiaEnv :: Lang -> (Text, Text)
toPolyglossiaEnv :: Lang -> (Text, Text)
toPolyglossiaEnv Lang
l =
case Lang -> (Text, Text)
toPolyglossia Lang
l of
(Text
"arabic", Text
o) -> (Text
"Arabic", Text
o)
(Text, Text)
x -> (Text, Text)
x
toPolyglossia :: Lang -> (Text, Text)
toPolyglossia :: Lang -> (Text, Text)
toPolyglossia (Lang Text
"ar" Maybe Text
_ (Just Text
"DZ") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"arabic", Text
"locale=algeria")
toPolyglossia (Lang Text
"ar" Maybe Text
_ (Just Text
"IQ") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"arabic", Text
"locale=mashriq")
toPolyglossia (Lang Text
"ar" Maybe Text
_ (Just Text
"JO") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"arabic", Text
"locale=mashriq")
toPolyglossia (Lang Text
"ar" Maybe Text
_ (Just Text
"LB") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"arabic", Text
"locale=mashriq")
toPolyglossia (Lang Text
"ar" Maybe Text
_ (Just Text
"LY") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"arabic", Text
"locale=libya")
toPolyglossia (Lang Text
"ar" Maybe Text
_ (Just Text
"MA") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"arabic", Text
"locale=morocco")
toPolyglossia (Lang Text
"ar" Maybe Text
_ (Just Text
"MR") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"arabic", Text
"locale=mauritania")
toPolyglossia (Lang Text
"ar" Maybe Text
_ (Just Text
"PS") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"arabic", Text
"locale=mashriq")
toPolyglossia (Lang Text
"ar" Maybe Text
_ (Just Text
"SY") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"arabic", Text
"locale=mashriq")
toPolyglossia (Lang Text
"ar" Maybe Text
_ (Just Text
"TN") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"arabic", Text
"locale=tunisia")
toPolyglossia (Lang Text
"de" Maybe Text
_ Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
| Text
"1901" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars = (Text
"german", Text
"spelling=old")
toPolyglossia (Lang Text
"de" Maybe Text
_ (Just Text
"AT") [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
| Text
"1901" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars = (Text
"german", Text
"variant=austrian, spelling=old")
toPolyglossia (Lang Text
"de" Maybe Text
_ (Just Text
"AT") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"german", Text
"variant=austrian")
toPolyglossia (Lang Text
"de" Maybe Text
_ (Just Text
"CH") [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
| Text
"1901" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars = (Text
"german", Text
"variant=swiss, spelling=old")
toPolyglossia (Lang Text
"de" Maybe Text
_ (Just Text
"CH") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"german", Text
"variant=swiss")
toPolyglossia (Lang Text
"de" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"german", Text
"")
toPolyglossia (Lang Text
"dsb" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"lsorbian", Text
"")
toPolyglossia (Lang Text
"el" Maybe Text
_ Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
| Text
"polyton" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars = (Text
"greek", Text
"variant=poly")
toPolyglossia (Lang Text
"en" Maybe Text
_ (Just Text
"AU") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"english", Text
"variant=australian")
toPolyglossia (Lang Text
"en" Maybe Text
_ (Just Text
"CA") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"english", Text
"variant=canadian")
toPolyglossia (Lang Text
"en" Maybe Text
_ (Just Text
"GB") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"english", Text
"variant=british")
toPolyglossia (Lang Text
"en" Maybe Text
_ (Just Text
"NZ") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"english", Text
"variant=newzealand")
toPolyglossia (Lang Text
"en" Maybe Text
_ (Just Text
"UK") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"english", Text
"variant=british")
toPolyglossia (Lang Text
"en" Maybe Text
_ (Just Text
"US") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"english", Text
"variant=american")
toPolyglossia (Lang Text
"grc" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"greek", Text
"variant=ancient")
toPolyglossia (Lang Text
"hsb" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"usorbian", Text
"")
toPolyglossia (Lang Text
"la" Maybe Text
_ Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
| Text
"x-classic" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars = (Text
"latin", Text
"variant=classic")
toPolyglossia (Lang Text
"pt" Maybe Text
_ (Just Text
"BR") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"portuguese", Text
"variant=brazilian")
toPolyglossia (Lang Text
"sl" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = (Text
"slovenian", Text
"")
toPolyglossia Lang
x = (Lang -> Text
commonFromBcp47 Lang
x, Text
"")
toBabel :: Lang -> Text
toBabel :: Lang -> Text
toBabel (Lang Text
"de" Maybe Text
_ (Just Text
"AT") [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
| Text
"1901" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars = Text
"austrian"
| Bool
otherwise = Text
"naustrian"
toBabel (Lang Text
"de" Maybe Text
_ (Just Text
"CH") [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
| Text
"1901" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars = Text
"swissgerman"
| Bool
otherwise = Text
"nswissgerman"
toBabel (Lang Text
"de" Maybe Text
_ Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
| Text
"1901" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars = Text
"german"
| Bool
otherwise = Text
"ngerman"
toBabel (Lang Text
"dsb" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"lowersorbian"
toBabel (Lang Text
"el" Maybe Text
_ Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
| Text
"polyton" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars = Text
"polutonikogreek"
toBabel (Lang Text
"en" Maybe Text
_ (Just Text
"AU") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"australian"
toBabel (Lang Text
"en" Maybe Text
_ (Just Text
"CA") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"canadian"
toBabel (Lang Text
"en" Maybe Text
_ (Just Text
"GB") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"british"
toBabel (Lang Text
"en" Maybe Text
_ (Just Text
"NZ") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"newzealand"
toBabel (Lang Text
"en" Maybe Text
_ (Just Text
"UK") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"british"
toBabel (Lang Text
"en" Maybe Text
_ (Just Text
"US") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"american"
toBabel (Lang Text
"fr" Maybe Text
_ (Just Text
"CA") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"canadien"
toBabel (Lang Text
"fra" Maybe Text
_ Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
| Text
"aca" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars = Text
"acadian"
toBabel (Lang Text
"grc" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"polutonikogreek"
toBabel (Lang Text
"hsb" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"uppersorbian"
toBabel (Lang Text
"la" Maybe Text
_ Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
| Text
"x-classic" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars = Text
"classiclatin"
toBabel (Lang Text
"pt" Maybe Text
_ (Just Text
"BR") [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"brazilian"
toBabel (Lang Text
"sl" Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"slovene"
toBabel Lang
x = Lang -> Text
commonFromBcp47 Lang
x
commonFromBcp47 :: Lang -> Text
commonFromBcp47 :: Lang -> Text
commonFromBcp47 (Lang Text
"sr" (Just Text
"Cyrl") Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text
"serbianc"
commonFromBcp47 (Lang Text
"zh" (Just Text
"Latn") Maybe Text
_ [Text]
vars [(Text, [(Text, Text)])]
_ [Text]
_)
| Text
"pinyin" Text -> [Text] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [Text]
vars = Text
"pinyin"
commonFromBcp47 (Lang Text
l Maybe Text
_ Maybe Text
_ [Text]
_ [(Text, [(Text, Text)])]
_ [Text]
_) = Text -> Text
forall a p. (Eq a, IsString a, IsString p) => a -> p
fromIso Text
l
where
fromIso :: a -> p
fromIso a
"af" = p
"afrikaans"
fromIso a
"am" = p
"amharic"
fromIso a
"ar" = p
"arabic"
fromIso a
"as" = p
"assamese"
fromIso a
"ast" = p
"asturian"
fromIso a
"bg" = p
"bulgarian"
fromIso a
"bn" = p
"bengali"
fromIso a
"bo" = p
"tibetan"
fromIso a
"br" = p
"breton"
fromIso a
"ca" = p
"catalan"
fromIso a
"cy" = p
"welsh"
fromIso a
"cs" = p
"czech"
fromIso a
"cop" = p
"coptic"
fromIso a
"da" = p
"danish"
fromIso a
"dv" = p
"divehi"
fromIso a
"el" = p
"greek"
fromIso a
"en" = p
"english"
fromIso a
"eo" = p
"esperanto"
fromIso a
"es" = p
"spanish"
fromIso a
"et" = p
"estonian"
fromIso a
"eu" = p
"basque"
fromIso a
"fa" = p
"farsi"
fromIso a
"fi" = p
"finnish"
fromIso a
"fr" = p
"french"
fromIso a
"fur" = p
"friulan"
fromIso a
"ga" = p
"irish"
fromIso a
"gd" = p
"scottish"
fromIso a
"gez" = p
"ethiopic"
fromIso a
"gl" = p
"galician"
fromIso a
"he" = p
"hebrew"
fromIso a
"hi" = p
"hindi"
fromIso a
"hr" = p
"croatian"
fromIso a
"hu" = p
"magyar"
fromIso a
"hy" = p
"armenian"
fromIso a
"ia" = p
"interlingua"
fromIso a
"id" = p
"indonesian"
fromIso a
"ie" = p
"interlingua"
fromIso a
"is" = p
"icelandic"
fromIso a
"it" = p
"italian"
fromIso a
"ja" = p
"japanese"
fromIso a
"km" = p
"khmer"
fromIso a
"kmr" = p
"kurmanji"
fromIso a
"kn" = p
"kannada"
fromIso a
"ko" = p
"korean"
fromIso a
"la" = p
"latin"
fromIso a
"lo" = p
"lao"
fromIso a
"lt" = p
"lithuanian"
fromIso a
"lv" = p
"latvian"
fromIso a
"ml" = p
"malayalam"
fromIso a
"mn" = p
"mongolian"
fromIso a
"mr" = p
"marathi"
fromIso a
"nb" = p
"norsk"
fromIso a
"nl" = p
"dutch"
fromIso a
"nn" = p
"nynorsk"
fromIso a
"no" = p
"norsk"
fromIso a
"nqo" = p
"nko"
fromIso a
"oc" = p
"occitan"
fromIso a
"pa" = p
"panjabi"
fromIso a
"pl" = p
"polish"
fromIso a
"pms" = p
"piedmontese"
fromIso a
"pt" = p
"portuguese"
fromIso a
"rm" = p
"romansh"
fromIso a
"ro" = p
"romanian"
fromIso a
"ru" = p
"russian"
fromIso a
"sa" = p
"sanskrit"
fromIso a
"se" = p
"samin"
fromIso a
"sk" = p
"slovak"
fromIso a
"sq" = p
"albanian"
fromIso a
"sr" = p
"serbian"
fromIso a
"sv" = p
"swedish"
fromIso a
"syr" = p
"syriac"
fromIso a
"ta" = p
"tamil"
fromIso a
"te" = p
"telugu"
fromIso a
"th" = p
"thai"
fromIso a
"ti" = p
"ethiopic"
fromIso a
"tk" = p
"turkmen"
fromIso a
"tr" = p
"turkish"
fromIso a
"uk" = p
"ukrainian"
fromIso a
"ur" = p
"urdu"
fromIso a
"vi" = p
"vietnamese"
fromIso a
_ = p
""