aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Shared.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/Shared.hs')
-rw-r--r--src/Text/Pandoc/Writers/Shared.hs26
1 files changed, 20 insertions, 6 deletions
diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs
index b399afbf3..0b7c6bee0 100644
--- a/src/Text/Pandoc/Writers/Shared.hs
+++ b/src/Text/Pandoc/Writers/Shared.hs
@@ -3,7 +3,7 @@
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Writers.Shared
- Copyright : Copyright (C) 2013-2020 John MacFarlane
+ Copyright : Copyright (C) 2013-2021 John MacFarlane
License : GNU GPL, version 2 or above
Maintainer : John MacFarlane <jgm@berkeley.edu>
@@ -20,6 +20,7 @@ module Text.Pandoc.Writers.Shared (
, setField
, resetField
, defField
+ , getLang
, tagWithAttrs
, isDisplayMath
, fixDisplayMath
@@ -44,6 +45,7 @@ import Control.Monad (zipWithM)
import Data.Aeson (ToJSON (..), encode)
import Data.Char (chr, ord, isSpace)
import Data.List (groupBy, intersperse, transpose, foldl')
+import Data.List.NonEmpty (NonEmpty(..), nonEmpty)
import Data.Text.Conversions (FromText(..))
import qualified Data.Map as M
import qualified Data.Text as T
@@ -109,8 +111,7 @@ metaValueToVal blockWriter inlineWriter (MetaMap metamap) =
MapVal . Context <$> mapM (metaValueToVal blockWriter inlineWriter) metamap
metaValueToVal blockWriter inlineWriter (MetaList xs) = ListVal <$>
mapM (metaValueToVal blockWriter inlineWriter) xs
-metaValueToVal _ _ (MetaBool True) = return $ SimpleVal "true"
-metaValueToVal _ _ (MetaBool False) = return NullVal
+metaValueToVal _ _ (MetaBool b) = return $ BoolVal b
metaValueToVal _ inlineWriter (MetaString s) =
SimpleVal <$> inlineWriter (Builder.toList (Builder.text s))
metaValueToVal blockWriter _ (MetaBlocks bs) = SimpleVal <$> blockWriter bs
@@ -147,6 +148,19 @@ defField field val (Context m) =
where
f _newval oldval = oldval
+-- | Get the contents of the `lang` metadata field or variable.
+getLang :: WriterOptions -> Meta -> Maybe T.Text
+getLang opts meta =
+ case lookupContext "lang" (writerVariables opts) of
+ Just s -> Just s
+ _ ->
+ case lookupMeta "lang" meta of
+ Just (MetaBlocks [Para [Str s]]) -> Just s
+ Just (MetaBlocks [Plain [Str s]]) -> Just s
+ Just (MetaInlines [Str s]) -> Just s
+ Just (MetaString s) -> Just s
+ _ -> Nothing
+
-- | Produce an HTML tag with the given pandoc attributes.
tagWithAttrs :: HasChars a => T.Text -> Attr -> Doc a
tagWithAttrs tag (ident,classes,kvs) = hsep
@@ -225,7 +239,7 @@ gridTable :: (Monad m, HasChars a)
-> m (Doc a)
gridTable opts blocksToDoc headless aligns widths headers rows = do
-- the number of columns will be used in case of even widths
- let numcols = maximum (length aligns : length widths :
+ let numcols = maximum (length aligns :| length widths :
map length (headers:rows))
let officialWidthsInChars widths' = map (
(\x -> if x < 1 then 1 else x) .
@@ -254,8 +268,7 @@ gridTable opts blocksToDoc headless aligns widths headers rows = do
let handleFullWidths widths' = do
rawHeaders' <- mapM (blocksToDoc opts) headers
rawRows' <- mapM (mapM (blocksToDoc opts)) rows
- let numChars [] = 0
- numChars xs = maximum . map offset $ xs
+ let numChars = maybe 0 maximum . nonEmpty . map offset
let minWidthsInChars =
map numChars $ transpose (rawHeaders' : rawRows')
let widthsInChars' = zipWith max
@@ -381,6 +394,7 @@ toSuperscript '2' = Just '\x00B2'
toSuperscript '3' = Just '\x00B3'
toSuperscript '+' = Just '\x207A'
toSuperscript '-' = Just '\x207B'
+toSuperscript '\x2212' = Just '\x207B' -- unicode minus
toSuperscript '=' = Just '\x207C'
toSuperscript '(' = Just '\x207D'
toSuperscript ')' = Just '\x207E'