hlint suggestions.

This commit is contained in:
John MacFarlane 2017-06-02 15:06:14 +02:00
parent 18f86a0c02
commit b61a51ee15
8 changed files with 37 additions and 36 deletions

View file

@ -40,3 +40,4 @@ import Text.Pandoc.Error (PandocError, handleError)
main :: IO ()
main = E.catch (parseOptions options defaultOpts >>= convertWithOpts)
(\(e :: PandocError) -> handleError (Left e))

View file

@ -1554,3 +1554,4 @@ splitField s =
case break (`elem` ":=") s of
(k,_:v) -> (k,v)
(k,[]) -> (k,"true")

View file

@ -11,7 +11,7 @@ import Text.Parsec.String
ruleParser :: Parser (String, String)
ruleParser = do
p <- many1 (noneOf ":") <* char ':'
v <- many1 (noneOf ":;") <* (optional $ char ';') <* spaces
v <- many1 (noneOf ":;") <* optional (char ';') <* spaces
return (trim p, trim v)
styleAttrParser :: Parser [(String, String)]

View file

@ -365,7 +365,7 @@ fillMediaBag sourceURL d = walkM handleImage d
let fname = basename <.> ext
insertMedia fname mt bs'
return $ Image attr lab (fname, tit))
(\e ->
(\e ->
case e of
PandocResourceNotFound _ -> do
report $ CouldNotFetchResource src

View file

@ -27,4 +27,4 @@ where
import Data.Time
import System.Locale ( defaultTimeLocale )
#endif
#endif

View file

@ -83,7 +83,7 @@ handleError (Left e) =
errColumn = sourceColumn errPos
ls = lines input ++ [""]
errorInFile = if length ls > errLine - 1
then concat ["\n", (ls !! (errLine - 1))
then concat ["\n", ls !! (errLine - 1)
,"\n", replicate (errColumn - 1) ' '
,"^"]
else ""

View file

@ -91,7 +91,7 @@ highlight syntaxmap formatter (_, classes, keyvals) rawCode =
, traceOutput = False }
classes' = map T.pack classes
rawCode' = T.pack rawCode
in case msum (map (\l -> lookupSyntax l syntaxmap) classes') of
in case msum (map ((`lookupSyntax` syntaxmap)) classes') of
Nothing
| numberLines fmtOpts -> Right
$ formatter fmtOpts{ codeClasses = [],
@ -100,9 +100,9 @@ highlight syntaxmap formatter (_, classes, keyvals) rawCode =
$ T.lines rawCode'
| otherwise -> Left ""
Just syntax ->
(formatter fmtOpts{ codeClasses =
formatter fmtOpts{ codeClasses =
[T.toLower (sShortname syntax)],
containerClasses = classes' }) <$>
containerClasses = classes' } <$>
tokenize tokenizeOpts syntax rawCode'
-- Functions for correlating latex listings package's language names

View file

@ -120,7 +120,7 @@ imageType img = case B.take 4 img of
| findSvgTag img
-> return Svg
"%!PS"
| (B.take 4 $ B.drop 1 $ B.dropWhile (/=' ') img) == "EPSF"
| B.take 4 (B.drop 1 $ B.dropWhile (/=' ') img) == "EPSF"
-> return Eps
_ -> mzero
@ -168,7 +168,7 @@ desiredSizeInPoints opts attr s =
(Nothing, Nothing) -> sizeInPoints s
where
ratio = fromIntegral (pxX s) / fromIntegral (pxY s)
getDim dir = case (dimension dir attr) of
getDim dir = case dimension dir attr of
Just (Percent _) -> Nothing
Just dim -> Just $ inPoints opts dim
Nothing -> Nothing
@ -182,7 +182,7 @@ inEm opts dim = (64/11) * inInch opts dim
inInch :: WriterOptions -> Dimension -> Double
inInch opts dim =
case dim of
(Pixel a) -> fromIntegral a / (fromIntegral $ writerDpi opts)
(Pixel a) -> fromIntegral a / fromIntegral (writerDpi opts)
(Centimeter a) -> a * 0.3937007874
(Inch a) -> a
(Percent _) -> 0
@ -261,7 +261,7 @@ epsSize img = do
case ls' of
[] -> mzero
(x:_) -> case B.words x of
(_:_:_:ux:uy:[]) -> do
[_, _, _, ux, uy] -> do
ux' <- safeRead $ B.unpack ux
uy' <- safeRead $ B.unpack uy
return ImageSize{
@ -279,27 +279,26 @@ pngSize img = do
let (i, rest') = B.splitAt 4 $ B.drop 4 rest
guard $ i == "MHDR" || i == "IHDR"
let (sizes, rest'') = B.splitAt 8 rest'
(x,y) <- case map fromIntegral $ unpack $ sizes of
(x,y) <- case map fromIntegral $unpack sizes of
([w1,w2,w3,w4,h1,h2,h3,h4] :: [Integer]) -> return
((shift w1 24) + (shift w2 16) + (shift w3 8) + w4,
(shift h1 24) + (shift h2 16) + (shift h3 8) + h4)
(shift w1 24 + shift w2 16 + shift w3 8 + w4,
shift h1 24 + shift h2 16 + shift h3 8 + h4)
_ -> Nothing -- "PNG parse error"
let (dpix, dpiy) = findpHYs rest''
return $ ImageSize { pxX = x, pxY = y, dpiX = dpix, dpiY = dpiy }
return ImageSize { pxX = x, pxY = y, dpiX = dpix, dpiY = dpiy }
findpHYs :: ByteString -> (Integer, Integer)
findpHYs x =
if B.null x || "IDAT" `B.isPrefixOf` x
then (72,72) -- default, no pHYs
else if "pHYs" `B.isPrefixOf` x
then let [x1,x2,x3,x4,y1,y2,y3,y4,u] = map fromIntegral
$ unpack $ B.take 9 $ B.drop 4 x
factor = if u == 1 -- dots per meter
then \z -> z * 254 `div` 10000
else const 72
in ( factor $ (shift x1 24) + (shift x2 16) + (shift x3 8) + x4,
factor $ (shift y1 24) + (shift y2 16) + (shift y3 8) + y4 )
else findpHYs $ B.drop 1 x -- read another byte
findpHYs x
| B.null x || "IDAT" `B.isPrefixOf` x = (72,72)
| "pHYs" `B.isPrefixOf` x =
let [x1,x2,x3,x4,y1,y2,y3,y4,u] =
map fromIntegral $ unpack $ B.take 9 $ B.drop 4 x
factor = if u == 1 -- dots per meter
then \z -> z * 254 `div` 10000
else const 72
in ( factor $ (shift x1 24) + (shift x2 16) + (shift x3 8) + x4,
factor $ (shift y1 24) + (shift y2 16) + (shift y3 8) + y4 )
| otherwise = findpHYs $ B.drop 1 x -- read another byte
gifSize :: ByteString -> Maybe ImageSize
gifSize img = do
@ -343,16 +342,16 @@ jpegSize img =
jfifSize :: ByteString -> Either String ImageSize
jfifSize rest =
let [dpiDensity,dpix1,dpix2,dpiy1,dpiy2] = map fromIntegral
$ unpack $ B.take 5 $ B.drop 9 $ rest
$ unpack $ B.take 5 $B.drop 9 rest
factor = case dpiDensity of
1 -> id
2 -> \x -> (x * 254 `div` 10)
2 -> \x -> x * 254 `div` 10
_ -> const 72
dpix = factor (shift dpix1 8 + dpix2)
dpiy = factor (shift dpiy1 8 + dpiy2)
in case findJfifSize rest of
Left msg -> Left msg
Right (w,h) -> Right $ ImageSize { pxX = w
Right (w,h) ->Right ImageSize { pxX = w
, pxY = h
, dpiX = dpix
, dpiY = dpiy }
@ -386,7 +385,7 @@ runGet' p bl =
exifSize :: ByteString -> Either String ImageSize
exifSize bs = runGet' header $ bl
exifSize bs =runGet' header bl
where bl = BL.fromChunks [bs]
header = runExceptT $ exifHeader bl
-- NOTE: It would be nicer to do
@ -456,14 +455,13 @@ exifHeader hdr = do
Left msg -> throwError msg
Right x -> return x
return (tag, payload)
entries <- sequence $ replicate (fromIntegral numentries) ifdEntry
entries <- replicateM (fromIntegral numentries) ifdEntry
subentries <- case lookup ExifOffset entries of
Just (UnsignedLong offset') -> do
pos <- lift bytesRead
lift $ skip (fromIntegral offset' - (fromIntegral pos - 8))
numsubentries <- lift getWord16
sequence $
replicate (fromIntegral numsubentries) ifdEntry
replicateM (fromIntegral numsubentries) ifdEntry
_ -> return []
let allentries = entries ++ subentries
(wdth, hght) <- case (lookup ExifImageWidth allentries,
@ -474,13 +472,13 @@ exifHeader hdr = do
-- we return a default width and height when
-- the exif header doesn't contain these
let resfactor = case lookup ResolutionUnit allentries of
Just (UnsignedShort 1) -> (100 / 254)
Just (UnsignedShort 1) -> 100 / 254
_ -> 1
let xres = maybe 72 (\(UnsignedRational x) -> floor $ x * resfactor)
$ lookup XResolution allentries
let yres = maybe 72 (\(UnsignedRational x) -> floor $ x * resfactor)
$ lookup YResolution allentries
return $ ImageSize{
return ImageSize{
pxX = wdth
, pxY = hght
, dpiX = xres
@ -604,3 +602,4 @@ tagTypeTable = M.fromList
, (0xa300, FileSource)
, (0xa301, SceneType)
]