ImageSize: make imageSize return an Either, not a Maybe.

This will give us better error reporting options.
This is part of a fix for #1834.
This commit is contained in:
John MacFarlane 2015-05-09 21:32:31 -07:00
parent 7920a1a469
commit 6fe243abbd
4 changed files with 22 additions and 16 deletions

View file

@ -70,15 +70,17 @@ imageType img = case B.take 4 img of
-> return Eps
_ -> (hush . Left) "Unknown image type"
imageSize :: ByteString -> Maybe ImageSize
imageSize img = do
t <- imageType img
case t of
Png -> pngSize img
Gif -> gifSize img
Jpeg -> jpegSize img
Eps -> epsSize img
Pdf -> Nothing -- TODO
imageSize :: ByteString -> Either String ImageSize
imageSize img =
case imageType img of
Just Png -> mbToEither "could not determine PNG size" $ pngSize img
Just Gif -> mbToEither "could not determine GIF size" $ gifSize img
Just Jpeg -> mbToEither "could not determine JPEG size" $ jpegSize img
Just Eps -> mbToEither "could not determine EPS size" $ epsSize img
Just Pdf -> Left "could not determine PDF size" -- TODO
Nothing -> Left "could not determine image type"
where mbToEither msg Nothing = Left msg
mbToEither _ (Just x) = Right x
defaultSize :: (Integer, Integer)
defaultSize = (72, 72)

View file

@ -1120,8 +1120,10 @@ inlineToOpenXML opts (Image alt (src, tit)) = do
inlinesToOpenXML opts alt
Right (img, mt) -> do
ident <- ("rId"++) `fmap` getUniqueId
let size = imageSize img
let (xpt,ypt) = maybe (120,120) sizeInPoints size
(xpt,ypt) <- case imageSize img of
Right size -> return $ sizeInPoints size
Left msg -> do liftIO (warn msg)
return (120,120)
-- 12700 emu = 1 pt
let (xemu,yemu) = fitToPage (xpt * 12700, ypt * 12700) (pageWidth * 12700)
let cNvPicPr = mknode "pic:cNvPicPr" [] $

View file

@ -134,8 +134,10 @@ transformPicMath opts entriesRef (Image lab (src,t)) = do
warn $ "Could not find image `" ++ src ++ "', skipping..."
return $ Emph lab
Right (img, mbMimeType) -> do
let size = imageSize img
let (w,h) = fromMaybe (0,0) $ sizeInPoints `fmap` size
(w,h) <- case imageSize img of
Right size -> return $ sizeInPoints size
Left msg -> do warn msg
return (0,0)
let tit' = show w ++ "x" ++ show h
entries <- readIORef entriesRef
let extension = fromMaybe (takeExtension $ takeWhile (/='?') src)

View file

@ -56,9 +56,9 @@ rtfEmbedImage opts x@(Image _ (src,_)) = do
"image/jpeg" -> "\\jpegblip"
"image/png" -> "\\pngblip"
_ -> error "Unknown file type"
let sizeSpec = case imageSize imgdata of
Nothing -> ""
Just sz -> "\\picw" ++ show xpx ++
sizeSpec <- case imageSize imgdata of
Left msg -> warn msg >> return ""
Right sz -> return $ "\\picw" ++ show xpx ++
"\\pich" ++ show ypx ++
"\\picwgoal" ++ show (xpt * 20)
++ "\\pichgoal" ++ show (ypt * 20)