aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/ImageSize.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Text/Pandoc/ImageSize.hs')
-rw-r--r--src/Text/Pandoc/ImageSize.hs20
1 files changed, 18 insertions, 2 deletions
diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs
index 4d914a10c..eec8658c5 100644
--- a/src/Text/Pandoc/ImageSize.hs
+++ b/src/Text/Pandoc/ImageSize.hs
@@ -43,6 +43,7 @@ module Text.Pandoc.ImageSize ( ImageType(..)
, inInch
, inPixel
, inPoints
+ , inEm
, numUnit
, showInInch
, showInPixel
@@ -80,12 +81,14 @@ data Dimension = Pixel Integer
| Centimeter Double
| Inch Double
| Percent Double
+ | Em Double
instance Show Dimension where
show (Pixel a) = show a ++ "px"
show (Centimeter a) = showFl a ++ "cm"
show (Inch a) = showFl a ++ "in"
show (Percent a) = show a ++ "%"
+ show (Em a) = showFl a ++ "em"
data ImageSize = ImageSize{
pxX :: Integer
@@ -97,7 +100,13 @@ instance Default ImageSize where
def = ImageSize 300 200 72 72
showFl :: (RealFloat a) => a -> String
-showFl a = showFFloat (Just 5) a ""
+showFl a = removeExtra0s $ showFFloat (Just 5) a ""
+
+removeExtra0s :: String -> String
+removeExtra0s s =
+ case dropWhile (=='0') $ reverse s of
+ '.':xs -> reverse xs
+ xs -> reverse xs
imageType :: ByteString -> Maybe ImageType
imageType img = case B.take 4 img of
@@ -167,6 +176,9 @@ desiredSizeInPoints opts attr s =
inPoints :: WriterOptions -> Dimension -> Double
inPoints opts dim = 72 * inInch opts dim
+inEm :: WriterOptions -> Dimension -> Double
+inEm opts dim = (64/11) * inInch opts dim
+
inInch :: WriterOptions -> Dimension -> Double
inInch opts dim =
case dim of
@@ -174,6 +186,7 @@ inInch opts dim =
(Centimeter a) -> a * 0.3937007874
(Inch a) -> a
(Percent _) -> 0
+ (Em a) -> a * (11/64)
inPixel :: WriterOptions -> Dimension -> Integer
inPixel opts dim =
@@ -181,7 +194,8 @@ inPixel opts dim =
(Pixel a) -> a
(Centimeter a) -> floor $ dpi * a * 0.3937007874 :: Integer
(Inch a) -> floor $ dpi * a :: Integer
- _ -> 0
+ (Percent _) -> 0
+ (Em a) -> floor $ dpi * a * (11/64) :: Integer
where
dpi = fromIntegral $ writerDpi opts
@@ -213,6 +227,7 @@ scaleDimension factor dim =
Centimeter x -> Centimeter (factor * x)
Inch x -> Inch (factor * x)
Percent x -> Percent (factor * x)
+ Em x -> Em (factor * x)
-- | Read a Dimension from an Attr attribute.
-- `dimension Width attr` might return `Just (Pixel 3)` or for example `Just (Centimeter 2.0)`, etc.
@@ -236,6 +251,7 @@ lengthToDim s = numUnit s >>= uncurry toDim
toDim a "" = Just $ Pixel (floor a::Integer)
toDim a "pt" = Just $ Inch (a / 72)
toDim a "pc" = Just $ Inch (a / 6)
+ toDim a "em" = Just $ Em a
toDim _ _ = Nothing
epsSize :: ByteString -> Maybe ImageSize