Skip to content

Commit

Permalink
Replace read with safeRead (#5186)
Browse files Browse the repository at this point in the history
closes #5180
  • Loading branch information
mb21 authored and jgm committed Dec 31, 2018
1 parent a1ad5bb commit c8b79b0
Show file tree
Hide file tree
Showing 3 changed files with 18 additions and 13 deletions.
9 changes: 6 additions & 3 deletions src/Text/Pandoc/Readers/TikiWiki.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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)

Expand Down Expand Up @@ -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
Expand Down
10 changes: 5 additions & 5 deletions src/Text/Pandoc/Writers/Docx.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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
Expand Down
12 changes: 7 additions & 5 deletions src/Text/Pandoc/Writers/LaTeX.hs
Original file line number Diff line number Diff line change
Expand Up @@ -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"
Expand Down

0 comments on commit c8b79b0

Please sign in to comment.