aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers')
-rw-r--r--src/Text/Pandoc/Writers/BibTeX.hs2
-rw-r--r--src/Text/Pandoc/Writers/ConTeXt.hs48
-rw-r--r--src/Text/Pandoc/Writers/CslJson.hs7
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs2
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs2
-rw-r--r--src/Text/Pandoc/Writers/LaTeX/Lang.hs8
-rw-r--r--src/Text/Pandoc/Writers/ODT.hs7
-rw-r--r--src/Text/Pandoc/Writers/OpenDocument.hs8
-rw-r--r--src/Text/Pandoc/Writers/Shared.hs2
9 files changed, 44 insertions, 42 deletions
diff --git a/src/Text/Pandoc/Writers/BibTeX.hs b/src/Text/Pandoc/Writers/BibTeX.hs
index b9ae0c13a..95de6b71f 100644
--- a/src/Text/Pandoc/Writers/BibTeX.hs
+++ b/src/Text/Pandoc/Writers/BibTeX.hs
@@ -43,7 +43,7 @@ writeBibTeX' :: PandocMonad m => Variant -> WriterOptions -> Pandoc -> m Text
writeBibTeX' variant opts (Pandoc meta _) = do
let mblang = case lookupMetaString "lang" meta of
"" -> Nothing
- t -> Just $ parseLang t
+ t -> either (const Nothing) Just $ parseLang t
let refs = case lookupMeta "references" meta of
Just (MetaList xs) -> mapMaybe metaValueToReference xs
_ -> []
diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs
index 3c9975be8..f352c84bc 100644
--- a/src/Text/Pandoc/Writers/ConTeXt.hs
+++ b/src/Text/Pandoc/Writers/ConTeXt.hs
@@ -21,7 +21,7 @@ import Data.Maybe (mapMaybe)
import Data.Text (Text)
import qualified Data.Text as T
import Network.URI (unEscapeString)
-import Text.Pandoc.BCP47
+import UnicodeCollation.Lang (Lang(..))
import Text.Pandoc.Class.PandocMonad (PandocMonad, report, toLang)
import Text.Pandoc.Definition
import Text.Pandoc.ImageSize
@@ -555,26 +555,26 @@ fromBCP47 mbs = fromBCP47' <$> toLang mbs
-- https://tools.ietf.org/html/bcp47#section-2.1
-- http://wiki.contextgarden.net/Language_Codes
fromBCP47' :: Maybe Lang -> Maybe Text
-fromBCP47' (Just (Lang "ar" _ "SY" _) ) = Just "ar-sy"
-fromBCP47' (Just (Lang "ar" _ "IQ" _) ) = Just "ar-iq"
-fromBCP47' (Just (Lang "ar" _ "JO" _) ) = Just "ar-jo"
-fromBCP47' (Just (Lang "ar" _ "LB" _) ) = Just "ar-lb"
-fromBCP47' (Just (Lang "ar" _ "DZ" _) ) = Just "ar-dz"
-fromBCP47' (Just (Lang "ar" _ "MA" _) ) = Just "ar-ma"
-fromBCP47' (Just (Lang "de" _ _ ["1901"]) ) = Just "deo"
-fromBCP47' (Just (Lang "de" _ "DE" _) ) = Just "de-de"
-fromBCP47' (Just (Lang "de" _ "AT" _) ) = Just "de-at"
-fromBCP47' (Just (Lang "de" _ "CH" _) ) = Just "de-ch"
-fromBCP47' (Just (Lang "el" _ _ ["poly"]) ) = Just "agr"
-fromBCP47' (Just (Lang "en" _ "US" _) ) = Just "en-us"
-fromBCP47' (Just (Lang "en" _ "GB" _) ) = Just "en-gb"
-fromBCP47' (Just (Lang "grc"_ _ _) ) = Just "agr"
-fromBCP47' (Just (Lang "el" _ _ _) ) = Just "gr"
-fromBCP47' (Just (Lang "eu" _ _ _) ) = Just "ba"
-fromBCP47' (Just (Lang "he" _ _ _) ) = Just "il"
-fromBCP47' (Just (Lang "jp" _ _ _) ) = Just "ja"
-fromBCP47' (Just (Lang "uk" _ _ _) ) = Just "ua"
-fromBCP47' (Just (Lang "vi" _ _ _) ) = Just "vn"
-fromBCP47' (Just (Lang "zh" _ _ _) ) = Just "cn"
-fromBCP47' (Just (Lang l _ _ _) ) = Just l
-fromBCP47' Nothing = Nothing
+fromBCP47' (Just (Lang "ar" _ (Just "SY") _ _ _)) = Just "ar-sy"
+fromBCP47' (Just (Lang "ar" _ (Just "IQ") _ _ _)) = Just "ar-iq"
+fromBCP47' (Just (Lang "ar" _ (Just "JO") _ _ _)) = Just "ar-jo"
+fromBCP47' (Just (Lang "ar" _ (Just "LB") _ _ _)) = Just "ar-lb"
+fromBCP47' (Just (Lang "ar" _ (Just "DZ") _ _ _)) = Just "ar-dz"
+fromBCP47' (Just (Lang "ar" _ (Just "MA") _ _ _)) = Just "ar-ma"
+fromBCP47' (Just (Lang "de" _ _ ["1901"] _ _)) = Just "deo"
+fromBCP47' (Just (Lang "de" _ (Just "DE") _ _ _)) = Just "de-de"
+fromBCP47' (Just (Lang "de" _ (Just "AT") _ _ _)) = Just "de-at"
+fromBCP47' (Just (Lang "de" _ (Just "CH") _ _ _)) = Just "de-ch"
+fromBCP47' (Just (Lang "el" _ _ ["poly"] _ _)) = Just "agr"
+fromBCP47' (Just (Lang "en" _ (Just "US") _ _ _)) = Just "en-us"
+fromBCP47' (Just (Lang "en" _ (Just "GB") _ _ _)) = Just "en-gb"
+fromBCP47' (Just (Lang "grc"_ _ _ _ _)) = Just "agr"
+fromBCP47' (Just (Lang "el" _ _ _ _ _)) = Just "gr"
+fromBCP47' (Just (Lang "eu" _ _ _ _ _)) = Just "ba"
+fromBCP47' (Just (Lang "he" _ _ _ _ _)) = Just "il"
+fromBCP47' (Just (Lang "jp" _ _ _ _ _)) = Just "ja"
+fromBCP47' (Just (Lang "uk" _ _ _ _ _)) = Just "ua"
+fromBCP47' (Just (Lang "vi" _ _ _ _ _)) = Just "vn"
+fromBCP47' (Just (Lang "zh" _ _ _ _ _)) = Just "cn"
+fromBCP47' (Just (Lang l _ _ _ _ _)) = Just l
+fromBCP47' Nothing = Nothing
diff --git a/src/Text/Pandoc/Writers/CslJson.hs b/src/Text/Pandoc/Writers/CslJson.hs
index a10def95e..395335667 100644
--- a/src/Text/Pandoc/Writers/CslJson.hs
+++ b/src/Text/Pandoc/Writers/CslJson.hs
@@ -34,15 +34,16 @@ import Control.Monad.Identity
import Citeproc.Locale (getLocale)
import Citeproc.CslJson
import Text.Pandoc.Options (WriterOptions)
-import Data.Maybe (mapMaybe)
+import Data.Maybe (mapMaybe, fromMaybe)
import Data.Aeson.Encode.Pretty (Config (..), Indent (Spaces),
NumberFormat (Generic),
defConfig, encodePretty')
writeCslJson :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeCslJson _opts (Pandoc meta _) = do
- let lang = maybe (Lang "en" (Just "US")) parseLang
- (lookupMeta "lang" meta >>= metaValueToText)
+ let lang = fromMaybe (Lang "en" Nothing (Just "US") [] [] [])
+ (lookupMeta "lang" meta >>= metaValueToText >>=
+ either (const Nothing) Just . parseLang)
locale <- case getLocale lang of
Left e -> throwError $ PandocCiteprocError e
Right l -> return l
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index 20bcd0324..7781df8e7 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -36,7 +36,7 @@ import qualified Data.Text.Lazy as TL
import Data.Time.Clock.POSIX
import Data.Digest.Pure.SHA (sha1, showDigest)
import Skylighting
-import Text.Pandoc.BCP47 (getLang, renderLang)
+import UnicodeCollation.Lang (renderLang)
import Text.Pandoc.Class.PandocMonad (PandocMonad, report, toLang)
import qualified Text.Pandoc.Class.PandocMonad as P
import Data.Time
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index 1c970e6ad..e99bad738 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -29,7 +29,7 @@ import qualified Data.Text as T
import Network.URI (unEscapeString)
import Text.DocTemplates (FromContext(lookupContext), renderTemplate,
Val(..), Context(..))
-import Text.Pandoc.BCP47 (Lang (..), getLang, renderLang)
+import UnicodeCollation.Lang (Lang (..), renderLang)
import Text.Pandoc.Class.PandocMonad (PandocMonad, report, toLang)
import Text.Pandoc.Definition
import Text.Pandoc.Highlighting (formatLaTeXBlock, formatLaTeXInline, highlight,
diff --git a/src/Text/Pandoc/Writers/LaTeX/Lang.hs b/src/Text/Pandoc/Writers/LaTeX/Lang.hs
index 871b2692a..437b84120 100644
--- a/src/Text/Pandoc/Writers/LaTeX/Lang.hs
+++ b/src/Text/Pandoc/Writers/LaTeX/Lang.hs
@@ -46,7 +46,7 @@ toPolyglossia (Lang "de" _ (Just "AT") vars _ _)
toPolyglossia (Lang "de" _ (Just "AT") _ _ _) = ("german", "variant=austrian")
toPolyglossia (Lang "de" _ (Just "CH") vars _ _)
| "1901" `elem` vars = ("german", "variant=swiss, spelling=old")
-toPolyglossia (Lang "de" _ (Just "CH") _ _ _ _) = ("german", "variant=swiss")
+toPolyglossia (Lang "de" _ (Just "CH") _ _ _) = ("german", "variant=swiss")
toPolyglossia (Lang "de" _ _ _ _ _) = ("german", "")
toPolyglossia (Lang "dsb" _ _ _ _ _) = ("lsorbian", "")
toPolyglossia (Lang "el" _ _ vars _ _)
@@ -61,9 +61,9 @@ toPolyglossia (Lang "grc" _ _ _ _ _) = ("greek", "variant=ancient")
toPolyglossia (Lang "hsb" _ _ _ _ _) = ("usorbian", "")
toPolyglossia (Lang "la" _ _ vars _ _)
| "x-classic" `elem` vars = ("latin", "variant=classic")
-toPolyglossia (Lang "pt" _ "BR" _ _ _) = ("portuguese", "variant=brazilian")
+toPolyglossia (Lang "pt" _ (Just "BR") _ _ _) = ("portuguese", "variant=brazilian")
toPolyglossia (Lang "sl" _ _ _ _ _) = ("slovenian", "")
-toPolyglossia x = (commonFromBcp47 x, "")
+toPolyglossia x = (commonFromBcp47 x, "")
-- Takes a list of the constituents of a BCP47 language code and
-- converts it to a Babel language string.
@@ -81,7 +81,7 @@ toBabel (Lang "de" _ _ vars _ _)
| "1901" `elem` vars = "german"
| otherwise = "ngerman"
toBabel (Lang "dsb" _ _ _ _ _) = "lowersorbian"
-toBabel (Lang "el" _ _ vars)
+toBabel (Lang "el" _ _ vars _ _)
| "polyton" `elem` vars = "polutonikogreek"
toBabel (Lang "en" _ (Just "AU") _ _ _) = "australian"
toBabel (Lang "en" _ (Just "CA") _ _ _) = "canadian"
diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs
index 101b236aa..6fd4cdeb4 100644
--- a/src/Text/Pandoc/Writers/ODT.hs
+++ b/src/Text/Pandoc/Writers/ODT.hs
@@ -16,6 +16,7 @@ import Codec.Archive.Zip
import Control.Monad.Except (catchError, throwError)
import Control.Monad.State.Strict
import qualified Data.ByteString.Lazy as B
+import Data.Maybe (fromMaybe)
import Data.Generics (everywhere', mkT)
import Data.List (isPrefixOf)
import qualified Data.Map as Map
@@ -23,7 +24,7 @@ import qualified Data.Text as T
import qualified Data.Text.Lazy as TL
import Data.Time
import System.FilePath (takeDirectory, takeExtension, (<.>))
-import Text.Pandoc.BCP47 (Lang (..), getLang, renderLang)
+import UnicodeCollation.Lang (Lang (..), renderLang)
import Text.Pandoc.Class.PandocMonad (PandocMonad, report, toLang)
import qualified Text.Pandoc.Class.PandocMonad as P
import Text.Pandoc.Definition
@@ -35,7 +36,7 @@ import Text.Pandoc.Options (WrapOption (..), WriterOptions (..))
import Text.DocLayout
import Text.Pandoc.Shared (stringify, pandocVersion, tshow)
import Text.Pandoc.Writers.Shared (lookupMetaString, lookupMetaBlocks,
- fixDisplayMath)
+ fixDisplayMath, getLang)
import Text.Pandoc.UTF8 (fromStringLazy, fromTextLazy, toTextLazy)
import Text.Pandoc.Walk
import Text.Pandoc.Writers.OpenDocument (writeOpenDocument)
@@ -194,7 +195,7 @@ addLang lang = everywhere' (mkT updateLangAttr)
where updateLangAttr (Attr n@(QName "language" _ (Just "fo")) _)
= Attr n (langLanguage lang)
updateLangAttr (Attr n@(QName "country" _ (Just "fo")) _)
- = Attr n (langRegion lang)
+ = Attr n (fromMaybe "" $ langRegion lang)
updateLangAttr x = x
-- | transform both Image and Math elements
diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs
index cf42f2228..6c265090c 100644
--- a/src/Text/Pandoc/Writers/OpenDocument.hs
+++ b/src/Text/Pandoc/Writers/OpenDocument.hs
@@ -25,7 +25,7 @@ import Data.Ord (comparing)
import qualified Data.Set as Set
import Data.Text (Text)
import qualified Data.Text as T
-import Text.Pandoc.BCP47 (Lang (..), parseBCP47)
+import UnicodeCollation.Lang (Lang (..), parseLang)
import Text.Pandoc.Class.PandocMonad (PandocMonad, report, translateTerm,
setTranslations, toLang)
import Text.Pandoc.Definition
@@ -236,7 +236,7 @@ handleSpaces s = case T.uncons s of
-- | Convert Pandoc document to string in OpenDocument format.
writeOpenDocument :: PandocMonad m => WriterOptions -> Pandoc -> m Text
writeOpenDocument opts (Pandoc meta blocks) = do
- let defLang = Lang "en" "US" "" []
+ let defLang = Lang "en" (Just "US") Nothing [] [] []
lang <- case lookupMetaString "lang" meta of
"" -> pure defLang
s -> fromMaybe defLang <$> toLang (Just s)
@@ -893,7 +893,7 @@ textStyleAttr m s
Map.insert "style:font-name-complex" "Courier New" $ m
| Language lang <- s
= Map.insert "fo:language" (langLanguage lang) .
- Map.insert "fo:country" (langRegion lang) $ m
+ maybe id (Map.insert "fo:country") (langRegion lang) $ m
| otherwise = m
withLangFromAttr :: PandocMonad m => Attr -> OD m a -> OD m a
@@ -901,7 +901,7 @@ withLangFromAttr (_,_,kvs) action =
case lookup "lang" kvs of
Nothing -> action
Just l ->
- case parseBCP47 l of
+ case parseLang l of
Right lang -> withTextStyle (Language lang) action
Left _ -> do
report $ InvalidLang l
diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs
index fcb47bd5a..a09d18571 100644
--- a/src/Text/Pandoc/Writers/Shared.hs
+++ b/src/Text/Pandoc/Writers/Shared.hs
@@ -149,7 +149,7 @@ defField field val (Context m) =
f _newval oldval = oldval
-- | Get the contents of the `lang` metadata field or variable.
-getLang :: WriterOptions -> Meta -> Maybe Text
+getLang :: WriterOptions -> Meta -> Maybe T.Text
getLang opts meta =
case lookupContext "lang" (writerVariables opts) of
Just s -> Just s