aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/Texinfo.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/Writers/Texinfo.hs')
-rw-r--r--src/Text/Pandoc/Writers/Texinfo.hs39
1 files changed, 23 insertions, 16 deletions
diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs
index c6debd9ce..6a33b4283 100644
--- a/src/Text/Pandoc/Writers/Texinfo.hs
+++ b/src/Text/Pandoc/Writers/Texinfo.hs
@@ -1,7 +1,7 @@
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Writers.Texinfo
- Copyright : Copyright (C) 2008-2020 John MacFarlane
+ Copyright : Copyright (C) 2008-2021 John MacFarlane
2012 Peter Wang
License : GNU GPL, version 2 or above
@@ -14,8 +14,9 @@ Conversion of 'Pandoc' format into Texinfo.
module Text.Pandoc.Writers.Texinfo ( writeTexinfo ) where
import Control.Monad.Except (throwError)
import Control.Monad.State.Strict
-import Data.Char (chr, ord)
-import Data.List (maximumBy, transpose)
+import Data.Char (chr, ord, isAlphaNum)
+import Data.List (maximumBy, transpose, foldl')
+import Data.List.NonEmpty (nonEmpty)
import Data.Ord (comparing)
import qualified Data.Set as Set
import Data.Text (Text)
@@ -84,16 +85,18 @@ pandocToTexinfo options (Pandoc meta blocks) = do
-- | Escape things as needed for Texinfo.
stringToTexinfo :: Text -> Text
-stringToTexinfo = escapeStringUsing texinfoEscapes
- where texinfoEscapes = [ ('{', "@{")
- , ('}', "@}")
- , ('@', "@@")
- , ('\160', "@ ")
- , ('\x2014', "---")
- , ('\x2013', "--")
- , ('\x2026', "@dots{}")
- , ('\x2019', "'")
- ]
+stringToTexinfo t
+ | T.all isAlphaNum t = t
+ | otherwise = T.concatMap escChar t
+ where escChar '{' = "@{"
+ escChar '}' = "@}"
+ escChar '@' = "@@"
+ escChar '\160' = "@ "
+ escChar '\x2014' = "---"
+ escChar '\x2013' = "--"
+ escChar '\x2026' = "@dots{}"
+ escChar '\x2019' = "'"
+ escChar c = T.singleton c
escapeCommas :: PandocMonad m => TI m (Doc Text) -> TI m (Doc Text)
escapeCommas parser = do
@@ -238,9 +241,13 @@ blockToTexinfo (Table _ blkCapt specs thead tbody tfoot) = do
colDescriptors <-
if all (== 0) widths
then do -- use longest entry instead of column widths
- cols <- mapM (mapM (liftM (T.unpack . render Nothing . hcat) . mapM blockToTexinfo)) $
+ cols <- mapM (mapM (fmap (T.unpack . render Nothing . hcat) .
+ mapM blockToTexinfo)) $
transpose $ heads : rows
- return $ concatMap ((\x -> "{"++x++"} ") . maximumBy (comparing length)) cols
+ return $ concatMap
+ ((\x -> "{"++x++"} ") .
+ maybe "" (maximumBy (comparing length)) . nonEmpty)
+ cols
else return $ "@columnfractions " ++ concatMap (printf "%.2f ") widths
let tableBody = text ("@multitable " ++ colDescriptors) $$
headers $$
@@ -271,7 +278,7 @@ tableAnyRowToTexinfo :: PandocMonad m
-> [[Block]]
-> TI m (Doc Text)
tableAnyRowToTexinfo itemtype aligns cols =
- (literal itemtype $$) . foldl (\row item -> row $$
+ (literal itemtype $$) . foldl' (\row item -> row $$
(if isEmpty row then empty else text " @tab ") <> item) empty <$> zipWithM alignedBlock aligns cols
alignedBlock :: PandocMonad m