aboutsummaryrefslogtreecommitdiff
path: root/src/Text
diff options
context:
space:
mode:
authorMauro Bieg <mb21@users.noreply.github.com>2019-01-01 00:26:38 +0100
committerJohn MacFarlane <jgm@berkeley.edu>2018-12-31 15:26:38 -0800
commitc8b79b0a04c113e0ea41099b0201576710158a49 (patch)
tree65140d6cadf55f70a3cf0a435930031fcde3e246 /src/Text
parenta1ad5bb8ceda50d7a4b2ef7da2a895e57ad12db4 (diff)
downloadpandoc-c8b79b0a04c113e0ea41099b0201576710158a49.tar.gz
Replace read with safeRead (#5186)
closes #5180
Diffstat (limited to 'src/Text')
-rw-r--r--src/Text/Pandoc/Readers/TikiWiki.hs9
-rw-r--r--src/Text/Pandoc/Writers/Docx.hs10
-rw-r--r--src/Text/Pandoc/Writers/LaTeX.hs12
3 files changed, 18 insertions, 13 deletions
diff --git a/src/Text/Pandoc/Readers/TikiWiki.hs b/src/Text/Pandoc/Readers/TikiWiki.hs
index 8458b05e5..8e01a80f8 100644
--- a/src/Text/Pandoc/Readers/TikiWiki.hs
+++ b/src/Text/Pandoc/Readers/TikiWiki.hs
@@ -32,7 +32,7 @@ import Text.Pandoc.Definition
import Text.Pandoc.Logging (Verbosity (..))
import Text.Pandoc.Options
import Text.Pandoc.Parsing hiding (enclosed, nested)
-import Text.Pandoc.Shared (crFilter)
+import Text.Pandoc.Shared (crFilter, safeRead)
import Text.Pandoc.XML (fromEntities)
import Text.Printf (printf)
@@ -500,9 +500,12 @@ emph = try $ fmap B.emph (enclosed (string "''") nestedInlines)
escapedChar :: PandocMonad m => TikiWikiParser m B.Inlines
escapedChar = try $ do
string "~"
- inner <- many1 $ oneOf "0123456789"
+ mNumber <- safeRead <$> many1 digit
string "~"
- return $B.str [toEnum (read inner :: Int) :: Char]
+ return $ B.str $
+ case mNumber of
+ Just number -> [toEnum (number :: Int) :: Char]
+ Nothing -> []
-- UNSUPPORTED, as there doesn't seem to be any facility in calibre
-- for this
diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs
index c2a160320..4f642871a 100644
--- a/src/Text/Pandoc/Writers/Docx.hs
+++ b/src/Text/Pandoc/Writers/Docx.hs
@@ -234,11 +234,11 @@ writeDocx opts doc@(Pandoc meta _) = do
-- Get the available area (converting the size and the margins to int and
-- doing the difference
- let pgContentWidth = (-) <$> (read <$> mbAttrSzWidth ::Maybe Integer)
- <*> (
- (+) <$> (read <$> mbAttrMarRight ::Maybe Integer)
- <*> (read <$> mbAttrMarLeft ::Maybe Integer)
- )
+ let pgContentWidth = mbAttrSzWidth >>= safeRead
+ >>= subtrct mbAttrMarRight
+ >>= subtrct mbAttrMarLeft
+ where
+ subtrct mbStr = \x -> mbStr >>= safeRead >>= (\y -> Just $ x - y)
-- styles
mblang <- toLang $ getLang opts meta
diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs
index ca8295f0a..f9bee886e 100644
--- a/src/Text/Pandoc/Writers/LaTeX.hs
+++ b/src/Text/Pandoc/Writers/LaTeX.hs
@@ -553,16 +553,18 @@ blockToLaTeX (Div (identifier,classes,kvs) bs)
else id
wrapColumn = if "column" `elem` classes
then \contents ->
- let fromPct xs =
- case reverse xs of
- '%':ds -> showFl (read (reverse ds) / 100 :: Double)
- _ -> xs
- w = maybe "0.48" fromPct (lookup "width" kvs)
+ let w = maybe "0.48" fromPct (lookup "width" kvs)
in inCmd "begin" "column" <>
braces (text w <> "\\textwidth")
$$ contents
$$ inCmd "end" "column"
else id
+ fromPct xs =
+ case reverse xs of
+ '%':ds -> case safeRead (reverse ds) of
+ Just digits -> showFl (digits / 100 :: Double)
+ Nothing -> xs
+ _ -> xs
wrapDir = case lookup "dir" kvs of
Just "rtl" -> align "RTL"
Just "ltr" -> align "LTR"